Copyright | (c) Eric Crockett 2011-2017 Chris Peikert 2011-2017 |
---|---|
License | GPL-3 |
Maintainer | ecrockett0@email.com |
Stability | experimental |
Portability | POSIX \( \def\Z{\mathbb{Z}} \) \( \def\C{\mathbb{C}} \) |
Safe Haskell | None |
Language | Haskell2010 |
Crypto.Lol.Prelude
Description
A substitute for the Prelude that is more suitable for Lol. This module exports most of the Numeric Prelude and other frequently used modules, plus some low-level classes, missing instances, and assorted utility functions.
Synopsis
- class Enumerable a where
- values :: [a]
- class (ToInteger (ModRep a), Additive a) => Mod a where
- class (Additive a, Additive b) => Subgroup a b where
- fromSubgroup :: a -> b
- class Reduce a b where
- reduce :: a -> b
- type family LiftOf b
- type Lift b a = (Lift' b, LiftOf b ~ a)
- class Reduce (LiftOf b) b => Lift' b where
- class (Additive a, Additive b) => Rescale a b where
- rescale :: a -> b
- class (Field src, Field tgt) => Encode src tgt where
- lsdToMSD :: (src, tgt)
- msdToLSD :: Encode src tgt => (src, tgt)
- type family CharOf fp :: k
- type Matrix a = T a
- type Polynomial a = T a
- type PID a = C a
- type RealIntegral a = C a
- type Absolute a = C a
- type ToInteger a = C a
- type OrdFloat a = (Ord a, Transcendental a)
- type RealTranscendental a = C a
- type Transcendental a = C a
- type Algebraic a = C a
- type RealField a = C a
- type RealRing a = C a
- type Field a = C a
- type ToRational a = C a
- type IntegralDomain a = C a
- type Module a v = C a v
- type Ring a = C a
- type Additive a = C a
- type ZeroTestable a = C a
- max :: Ord a => a -> a -> a
- min :: Ord a => a -> a -> a
- abs :: Absolute a => a -> a
- realToField :: (Field b, ToRational a) => a -> b
- (^) :: forall a i. (Ring a, ToInteger i) => a -> i -> a
- modinv :: (PID i, Eq i) => i -> i -> Maybe i
- decomp :: (IntegralDomain z, Ord z) => [z] -> z -> [z]
- roundMult :: (RealField r, ToInteger i) => i -> r -> i
- roundScalarCentered :: (RealField r, Random r, ToInteger i, MonadRandom mon) => i -> r -> mon i
- divModCent :: IntegralDomain i => i -> i -> (i, i)
- (++) :: [a] -> [a] -> [a]
- seq :: a -> b -> b
- filter :: (a -> Bool) -> [a] -> [a]
- zip :: [a] -> [b] -> [(a, b)]
- print :: Show a => a -> IO ()
- fst :: (a, b) -> a
- snd :: (a, b) -> b
- otherwise :: Bool
- map :: (a -> b) -> [a] -> [b]
- ($) :: (a -> b) -> a -> b
- realToFrac :: (Real a, Fractional b) => a -> b
- class Bounded a where
- class Enum a where
- succ :: a -> a
- pred :: a -> a
- toEnum :: Int -> a
- fromEnum :: a -> Int
- enumFrom :: a -> [a]
- enumFromThen :: a -> a -> [a]
- enumFromTo :: a -> a -> [a]
- enumFromThenTo :: a -> a -> a -> [a]
- class Eq a where
- class Applicative m => Monad (m :: Type -> Type) where
- class Functor (f :: Type -> Type) where
- class Eq a => Ord a where
- class Read a where
- class Show a where
- foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b
- length :: Foldable t => t a -> Int
- null :: Foldable t => t a -> Bool
- foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b
- foldl1 :: Foldable t => (a -> a -> a) -> t a -> a
- foldr1 :: Foldable t => (a -> a -> a) -> t a -> a
- maximum :: (Foldable t, Ord a) => t a -> a
- minimum :: (Foldable t, Ord a) => t a -> a
- elem :: (Foldable t, Eq a) => a -> t a -> Bool
- mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b)
- sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
- data Bool
- data Char
- data Double
- data Float
- data Int
- data Integer
- data Maybe a
- data Ordering
- data IO a
- data Either a b
- type FilePath = String
- error :: HasCallStack => [Char] -> a
- type String = [Char]
- (=<<) :: Monad m => (a -> m b) -> m a -> m b
- mapM_ :: (Foldable t, Monad m) => (a -> m b) -> t a -> m ()
- sequence_ :: (Foldable t, Monad m) => t (m a) -> m ()
- const :: a -> b -> a
- (.) :: (b -> c) -> (a -> b) -> a -> c
- id :: a -> a
- type ShowS = String -> String
- read :: Read a => String -> a
- readIO :: Read a => String -> IO a
- readLn :: Read a => IO a
- appendFile :: FilePath -> String -> IO ()
- writeFile :: FilePath -> String -> IO ()
- readFile :: FilePath -> IO String
- interact :: (String -> String) -> IO ()
- getContents :: IO String
- getLine :: IO String
- getChar :: IO Char
- putStrLn :: String -> IO ()
- putStr :: String -> IO ()
- putChar :: Char -> IO ()
- ioError :: IOError -> IO a
- userError :: String -> IOError
- type IOError = IOException
- notElem :: (Foldable t, Eq a) => a -> t a -> Bool
- all :: Foldable t => (a -> Bool) -> t a -> Bool
- any :: Foldable t => (a -> Bool) -> t a -> Bool
- or :: Foldable t => t Bool -> Bool
- and :: Foldable t => t Bool -> Bool
- concatMap :: Foldable t => (a -> [b]) -> t a -> [b]
- concat :: Foldable t => t [a] -> [a]
- unwords :: [String] -> String
- words :: String -> [String]
- unlines :: [String] -> String
- lines :: String -> [String]
- reads :: Read a => ReadS a
- either :: (a -> c) -> (b -> c) -> Either a b -> c
- lex :: ReadS String
- readParen :: Bool -> ReadS a -> ReadS a
- type ReadS a = String -> [(a, String)]
- showParen :: Bool -> ShowS -> ShowS
- showString :: String -> ShowS
- showChar :: Char -> ShowS
- shows :: Show a => a -> ShowS
- unzip3 :: [(a, b, c)] -> ([a], [b], [c])
- unzip :: [(a, b)] -> ([a], [b])
- zipWith3 :: (a -> b -> c -> d) -> [a] -> [b] -> [c] -> [d]
- zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
- zip3 :: [a] -> [b] -> [c] -> [(a, b, c)]
- (!!) :: [a] -> Int -> a
- lookup :: Eq a => a -> [(a, b)] -> Maybe b
- reverse :: [a] -> [a]
- break :: (a -> Bool) -> [a] -> ([a], [a])
- span :: (a -> Bool) -> [a] -> ([a], [a])
- splitAt :: Int -> [a] -> ([a], [a])
- drop :: Int -> [a] -> [a]
- take :: Int -> [a] -> [a]
- dropWhile :: (a -> Bool) -> [a] -> [a]
- takeWhile :: (a -> Bool) -> [a] -> [a]
- cycle :: [a] -> [a]
- replicate :: Int -> a -> [a]
- repeat :: a -> [a]
- iterate :: (a -> a) -> a -> [a]
- scanr1 :: (a -> a -> a) -> [a] -> [a]
- scanr :: (a -> b -> b) -> b -> [a] -> [b]
- scanl1 :: (a -> a -> a) -> [a] -> [a]
- scanl :: (b -> a -> b) -> b -> [a] -> [b]
- init :: [a] -> [a]
- last :: [a] -> a
- tail :: [a] -> [a]
- head :: [a] -> a
- maybe :: b -> (a -> b) -> Maybe a -> b
- uncurry :: (a -> b -> c) -> (a, b) -> c
- curry :: ((a, b) -> c) -> a -> b -> c
- asTypeOf :: a -> a -> a
- until :: (a -> Bool) -> (a -> a) -> a -> a
- ($!) :: (a -> b) -> a -> b
- flip :: (a -> b -> c) -> b -> a -> c
- undefined :: HasCallStack => a
- (&&) :: Bool -> Bool -> Bool
- (||) :: Bool -> Bool -> Bool
- not :: Bool -> Bool
- atan2 :: C a => a -> a -> a
- approxRational :: (C a, C a) => a -> a -> Rational
- truncate :: (C a, C b) => a -> b
- round :: (C a, C b) => a -> b
- ceiling :: (C a, C b) => a -> b
- floor :: (C a, C b) => a -> b
- splitFraction :: (C a, C b) => a -> (b, a)
- fraction :: C a => a -> a
- (^?) :: C a => a -> a -> a
- pi :: C a => a
- exp :: C a => a -> a
- log :: C a => a -> a
- (**) :: C a => a -> a -> a
- logBase :: C a => a -> a -> a
- sin :: C a => a -> a
- cos :: C a => a -> a
- tan :: C a => a -> a
- asin :: C a => a -> a
- acos :: C a => a -> a
- atan :: C a => a -> a
- sinh :: C a => a -> a
- cosh :: C a => a -> a
- tanh :: C a => a -> a
- asinh :: C a => a -> a
- acosh :: C a => a -> a
- atanh :: C a => a -> a
- sqrt :: C a => a -> a
- (^/) :: C a => a -> Rational -> a
- (*>) :: C a v => a -> v -> v
- fieldPower :: (C a, C b) => b -> a -> a
- ringPower :: (C a, C b) => b -> a -> a
- fromIntegral :: (C a, C b) => a -> b
- toInteger :: C a => a -> Integer
- quotRem :: C a => a -> a -> (a, a)
- quot :: C a => a -> a -> a
- rem :: C a => a -> a -> a
- toRational :: C a => a -> Rational
- fromRational :: C a => Rational -> a
- (/) :: C a => a -> a -> a
- recip :: C a => a -> a
- fromRational' :: C a => Rational -> a
- (^-) :: C a => a -> Integer -> a
- (%) :: C a => a -> a -> T a
- numerator :: T a -> a
- denominator :: T a -> a
- type Rational = T Integer
- signum :: C a => a -> a
- extendedEuclid :: (C a, C a) => (a -> a -> (a, a)) -> a -> a -> (a, (a, a))
- euclid :: (C a, C a) => (a -> a -> a) -> a -> a -> a
- gcd :: C a => a -> a -> a
- lcm :: C a => a -> a -> a
- extendedGCD :: C a => a -> a -> (a, (a, a))
- isUnit :: C a => a -> Bool
- stdAssociate :: C a => a -> a
- stdUnit :: C a => a -> a
- stdUnitInv :: C a => a -> a
- odd :: (C a, C a) => a -> Bool
- even :: (C a, C a) => a -> Bool
- divides :: (C a, C a) => a -> a -> Bool
- divMod :: C a => a -> a -> (a, a)
- div :: C a => a -> a -> a
- mod :: C a => a -> a -> a
- product1 :: C a => [a] -> a
- product :: C a => [a] -> a
- sqr :: C a => a -> a
- (*) :: C a => a -> a -> a
- fromInteger :: C a => Integer -> a
- one :: C a => a
- isZero :: C a => a -> Bool
- sum1 :: C a => [a] -> a
- sum :: C a => [a] -> a
- subtract :: C a => a -> a -> a
- (+) :: C a => a -> a -> a
- (-) :: C a => a -> a -> a
- negate :: C a => a -> a
- zero :: C a => a
- catch :: IO a -> (IOError -> IO a) -> IO a
- ifThenElse :: Bool -> a -> a -> a
- data Int64
- data Complex a
- roundComplex :: (RealRing a, ToInteger b) => Complex a -> (b, b)
- cis :: Transcendental a => a -> Complex a
- real :: Complex a -> a
- imag :: Complex a -> a
- fromReal :: Additive a => a -> Complex a
- module Crypto.Lol.Factored
- rescaleMod :: forall a b. (Mod a, Mod b, ModRep a ~ ModRep b, Lift a (ModRep b), Ring b) => a -> b
- roundCoset :: forall zp z r. (Mod zp, z ~ ModRep zp, Lift zp z, RealField r) => zp -> r -> z
- fromJust' :: String -> Maybe a -> a
- pureT :: Applicative f => Tagged t a -> TaggedT t f a
- peelT :: Tagged t (f a) -> TaggedT t f a
- pasteT :: TaggedT t f a -> Tagged t (f a)
- withWitness :: forall n r. (SingI n => Tagged n r) -> Sing n -> r
- withWitnessT :: forall n mon r. (SingI n => TaggedT n mon r) -> Sing n -> mon r
- module Data.Functor.Trans.Tagged
- module Data.Proxy
Classes and families
class Enumerable a where Source #
Poor man's Enum
.
class (ToInteger (ModRep a), Additive a) => Mod a where Source #
Represents a quotient group modulo some integer.
class (Additive a, Additive b) => Subgroup a b where Source #
Represents that a
is a subgroup of b
.
Methods
fromSubgroup :: a -> b Source #
class Reduce a b where Source #
Represents that b
is a quotient group of a
.
Instances
The type of representatives of b
.
Instances
type LiftOf (a, b) Source # | |
Defined in Crypto.Lol.Prelude | |
type LiftOf (ZqBasic q z) Source # | |
Defined in Crypto.Lol.Types.Unsafe.ZqBasic | |
type LiftOf (RRq q r) Source # | |
Defined in Crypto.Lol.Types.Unsafe.RRq | |
type LiftOf (Cyc t m r) Source # | |
Defined in Crypto.Lol.Cyclotomic.Cyc | |
type LiftOf (CycRep t D m r) Source # | |
type LiftOf (CycRep t P m r) Source # | |
type LiftOf (Linear c e r s zp) Source # | |
Defined in Crypto.Lol.Cyclotomic.Linear |
type Lift b a = (Lift' b, LiftOf b ~ a) Source #
Represents that b
can be lifted to a "short" a
congruent to b
.
class Reduce (LiftOf b) b => Lift' b where Source #
Fun-dep version of Lift.
Instances
(Mod a, Mod b, Lift' a, Lift' b, Reduce Integer (a, b), ToInteger (LiftOf a), ToInteger (LiftOf b)) => Lift' (a, b) Source # | Lift product ring of \(\Z_q\)s to |
Defined in Crypto.Lol.Prelude | |
(Reflects q z, Ring z, Ord z, IntegralDomain z) => Lift' (ZqBasic q z) Source # | |
(Reflects q r, Field r, Reduce r (RRq q r)) => Lift' (RRq q r) Source # | |
(Lift' r, IFunctor t, IFElt t r, IFElt t (LiftOf r), Fact m) => Lift' (CycRep t D m r) Source # | |
(Fact m, Lift' r, IFunctor t, IFElt t r, IFElt t (LiftOf r)) => Lift' (CycRep t P m r) Source # | |
class (Additive a, Additive b) => Rescale a b where Source #
Represents that a
can be rescaled to b
, as an "approximate"
additive homomorphism.
Instances
(Additive a, Rescale f (b, (c, (d, (e, f)))), Rescale (b, (c, (d, (e, f)))) (a, (b, (c, (d, (e, f)))))) => Rescale f (a, (b, (c, (d, (e, f))))) Source # | Rescale up by a product of five rings |
Defined in Crypto.Lol.Prelude | |
(Additive a, Rescale e (b, (c, (d, e))), Rescale (b, (c, (d, e))) (a, (b, (c, (d, e))))) => Rescale e (a, (b, (c, (d, e)))) Source # | Rescale up by a product of four rings |
Defined in Crypto.Lol.Prelude | |
(Additive a, Rescale d (b, (c, d)), Rescale (b, (c, d)) (a, (b, (c, d)))) => Rescale d (a, (b, (c, d))) Source # | Rescale up by a product of three rings |
Defined in Crypto.Lol.Prelude | |
(Additive a, Rescale c (b, c), Rescale (b, c) (a, (b, c))) => Rescale c (a, (b, c)) Source # | Rescale up by a product of two rings |
Defined in Crypto.Lol.Prelude | |
(Ring b, Mod a, Reduce (ModRep a) b) => Rescale b (a, b) Source # | Rescale up to a product ring of \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Ring a, Mod b, Reduce (ModRep b) a) => Rescale a (a, b) Source # | Rescale up to a product ring of \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Rescale ((a, b), c) (a, b), Rescale (a, b) a, Additive a, Additive c) => Rescale ((a, b), c) a Source # | Rescale a (multi-)product ring of \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Mod b, Field a, Lift b (ModRep b), Reduce (LiftOf b) a) => Rescale (a, b) a Source # | Rescale a product ring of \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Rescale (a, (b, (c, (d, (e, f))))) (b, (c, (d, (e, f)))), Rescale (b, (c, (d, (e, f)))) f, Additive a) => Rescale (a, (b, (c, (d, (e, f))))) f Source # | Rescale down by a product ring of five \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Rescale (a, (b, (c, (d, e)))) (b, (c, (d, e))), Rescale (b, (c, (d, e))) e, Additive a) => Rescale (a, (b, (c, (d, e)))) e Source # | Rescale down by a product ring of four \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Rescale (a, (b, (c, d))) (b, (c, d)), Rescale (b, (c, d)) d, Additive a) => Rescale (a, (b, (c, d))) d Source # | Rescale down by a product ring of three \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Rescale (a, (b, c)) (b, c), Rescale (b, c) c, Additive a, Additive c) => Rescale (a, (b, c)) c Source # | Rescale down by a product ring of two \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Mod a, Field b, Lift a (ModRep a), Reduce (LiftOf a) b) => Rescale (a, b) b Source # | Rescale a product ring of \(\Z_q\)s |
Defined in Crypto.Lol.Prelude | |
(Reflects q z, ToInteger z, Reflects q' z, Ring z) => Rescale (ZqBasic q z) (ZqBasic q' z) Source # | |
(Additive (RRq q r), Additive (RRq p r)) => Rescale (RRq q r) (RRq p r) Source # | |
(RescaleCyc (Cyc t m) a b, Fact m, Additive (Cyc t m a), Additive (Cyc t m b)) => Rescale (Cyc t m a) (Cyc t m b) Source # | Rescales relative to the powerful basis. This instance is
provided for convenience, but usage of |
(Rescale a b, TensorPowDec t a, TensorPowDec t b, Fact m) => Rescale (CycRep t D m a) (CycRep t D m b) Source # | |
(Rescale a b, TensorPowDec t a, TensorPowDec t b, Fact m) => Rescale (CycRep t P m a) (CycRep t P m b) Source # | |
class (Field src, Field tgt) => Encode src tgt where Source #
Represents that the target ring can "noisily encode" values from the source ring, in either "most significant digit" (MSD) or "least significant digit" (LSD) encodings, and provides conversion factors between the two types of encodings.
Methods
lsdToMSD :: (src, tgt) Source #
The factor that converts an element from LSD to MSD encoding in the target field, with associated scale factor to apply to correct the resulting encoded value.
Numeric
type Polynomial a = T a Source #
Sane synonym for T
.
type RealIntegral a = C a Source #
Sane synonym for C
.
type OrdFloat a = (Ord a, Transcendental a) Source #
Convenient synonym for (
Ord
a, Transcendental
a)
type RealTranscendental a = C a Source #
Sane synonym for C
.
type Transcendental a = C a Source #
Sane synonym for C
.
type ToRational a = C a Source #
Sane synonym for C
.
type IntegralDomain a = C a Source #
Sane synonym for C
.
type ZeroTestable a = C a Source #
Sane synonym for C
.
realToField :: (Field b, ToRational a) => a -> b Source #
The hidden NP function from Algebra.ToRational.
(^) :: forall a i. (Ring a, ToInteger i) => a -> i -> a Source #
Our custom exponentiation, overriding NP's version that
requires Integer
exponent.
Copied from http://hackage.haskell.org/package/base-4.7.0.0/docs/src/GHC-Real.html#%5E
modinv :: (PID i, Eq i) => i -> i -> Maybe i Source #
Inverse of \(a\) modulo \(q\), in range \([0,q-1]\). (Argument order is infix-friendly.)
decomp :: (IntegralDomain z, Ord z) => [z] -> z -> [z] Source #
Decompose an element into a list of "centered" digits with respect to relative radices.
roundMult :: (RealField r, ToInteger i) => i -> r -> i Source #
Deterministically round to the nearest multiple of \( i \).
roundScalarCentered :: (RealField r, Random r, ToInteger i, MonadRandom mon) => i -> r -> mon i Source #
Randomly round to the nearest larger or smaller multiple of \( i \), where the round-off term has expectation zero.
Arguments
:: IntegralDomain i | |
=> i | dividend \(a\) |
-> i | divisor \(b\) |
-> (i, i) | (quotient, remainder) |
Variant of divMod
in which the remainder
is in the range \([-b/2,b/2)\).
(++) :: [a] -> [a] -> [a] infixr 5 #
Append two lists, i.e.,
[x1, ..., xm] ++ [y1, ..., yn] == [x1, ..., xm, y1, ..., yn] [x1, ..., xm] ++ [y1, ...] == [x1, ..., xm, y1, ...]
If the first list is not finite, the result is the first list.
The value of seq a b
is bottom if a
is bottom, and
otherwise equal to b
. In other words, it evaluates the first
argument a
to weak head normal form (WHNF). seq
is usually
introduced to improve performance by avoiding unneeded laziness.
A note on evaluation order: the expression seq a b
does
not guarantee that a
will be evaluated before b
.
The only guarantee given by seq
is that the both a
and b
will be evaluated before seq
returns a value.
In particular, this means that b
may be evaluated before
a
. If you need to guarantee a specific order of evaluation,
you must use the function pseq
from the "parallel" package.
filter :: (a -> Bool) -> [a] -> [a] #
filter
, applied to a predicate and a list, returns the list of
those elements that satisfy the predicate; i.e.,
filter p xs = [ x | x <- xs, p x]
print :: Show a => a -> IO () #
The print
function outputs a value of any printable type to the
standard output device.
Printable types are those that are instances of class Show
; print
converts values to strings for output using the show
operation and
adds a newline.
For example, a program to print the first 20 integers and their powers of 2 could be written as:
main = print ([(n, 2^n) | n <- [0..19]])
map :: (a -> b) -> [a] -> [b] #
map
f xs
is the list obtained by applying f
to each element
of xs
, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
($) :: (a -> b) -> a -> b infixr 0 #
Application operator. This operator is redundant, since ordinary
application (f x)
means the same as (f
. However, $
x)$
has
low, right-associative binding precedence, so it sometimes allows
parentheses to be omitted; for example:
f $ g $ h x = f (g (h x))
It is also useful in higher-order situations, such as
,
or map
($
0) xs
.zipWith
($
) fs xs
Note that ($)
is levity-polymorphic in its result type, so that
foo $ True where foo :: Bool -> Int#
is well-typed
realToFrac :: (Real a, Fractional b) => a -> b #
general coercion to fractional types
The Bounded
class is used to name the upper and lower limits of a
type. Ord
is not a superclass of Bounded
since types that are not
totally ordered may also have upper and lower bounds.
The Bounded
class may be derived for any enumeration type;
minBound
is the first constructor listed in the data
declaration
and maxBound
is the last.
Bounded
may also be derived for single-constructor datatypes whose
constituent types are in Bounded
.
Instances
Class Enum
defines operations on sequentially ordered types.
The enumFrom
... methods are used in Haskell's translation of
arithmetic sequences.
Instances of Enum
may be derived for any enumeration type (types
whose constructors have no fields). The nullary constructors are
assumed to be numbered left-to-right by fromEnum
from 0
through n-1
.
See Chapter 10 of the Haskell Report for more details.
For any type that is an instance of class Bounded
as well as Enum
,
the following should hold:
- The calls
andsucc
maxBound
should result in a runtime error.pred
minBound
fromEnum
andtoEnum
should give a runtime error if the result value is not representable in the result type. For example,
is an error.toEnum
7 ::Bool
enumFrom
andenumFromThen
should be defined with an implicit bound, thus:
enumFrom x = enumFromTo x maxBound enumFromThen x y = enumFromThenTo x y bound where bound | fromEnum y >= fromEnum x = maxBound | otherwise = minBound
Methods
the successor of a value. For numeric types, succ
adds 1.
the predecessor of a value. For numeric types, pred
subtracts 1.
Convert from an Int
.
Convert to an Int
.
It is implementation-dependent what fromEnum
returns when
applied to a value that is too large to fit in an Int
.
Used in Haskell's translation of [n..]
with [n..] = enumFrom n
,
a possible implementation being enumFrom n = n : enumFrom (succ n)
.
For example:
enumFrom 4 :: [Integer] = [4,5,6,7,...]
enumFrom 6 :: [Int] = [6,7,8,9,...,maxBound :: Int]
enumFromThen :: a -> a -> [a] #
Used in Haskell's translation of [n,n'..]
with [n,n'..] = enumFromThen n n'
, a possible implementation being
enumFromThen n n' = n : n' : worker (f x) (f x n')
,
worker s v = v : worker s (s v)
, x = fromEnum n' - fromEnum n
and
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
For example:
enumFromThen 4 6 :: [Integer] = [4,6,8,10...]
enumFromThen 6 2 :: [Int] = [6,2,-2,-6,...,minBound :: Int]
enumFromTo :: a -> a -> [a] #
Used in Haskell's translation of [n..m]
with
[n..m] = enumFromTo n m
, a possible implementation being
enumFromTo n m
| n <= m = n : enumFromTo (succ n) m
| otherwise = []
.
For example:
enumFromTo 6 10 :: [Int] = [6,7,8,9,10]
enumFromTo 42 1 :: [Integer] = []
enumFromThenTo :: a -> a -> a -> [a] #
Used in Haskell's translation of [n,n'..m]
with
[n,n'..m] = enumFromThenTo n n' m
, a possible implementation
being enumFromThenTo n n' m = worker (f x) (c x) n m
,
x = fromEnum n' - fromEnum n
, c x = bool (>=) ((x 0)
f n y
| n > 0 = f (n - 1) (succ y)
| n < 0 = f (n + 1) (pred y)
| otherwise = y
and
worker s c v m
| c v m = v : worker s c (s v) m
| otherwise = []
For example:
enumFromThenTo 4 2 -6 :: [Integer] = [4,2,0,-2,-4,-6]
enumFromThenTo 6 8 2 :: [Int] = []
Instances
The Eq
class defines equality (==
) and inequality (/=
).
All the basic datatypes exported by the Prelude are instances of Eq
,
and Eq
may be derived for any datatype whose constituents are also
instances of Eq
.
The Haskell Report defines no laws for Eq
. However, ==
is customarily
expected to implement an equivalence relationship where two values comparing
equal are indistinguishable by "public" functions, with a "public" function
being one not allowing to see implementation details. For example, for a
type representing non-normalised natural numbers modulo 100, a "public"
function doesn't make the difference between 1 and 201. It is expected to
have the following properties:
Instances
class Applicative m => Monad (m :: Type -> Type) where #
The Monad
class defines the basic operations over a monad,
a concept from a branch of mathematics known as category theory.
From the perspective of a Haskell programmer, however, it is best to
think of a monad as an abstract datatype of actions.
Haskell's do
expressions provide a convenient syntax for writing
monadic expressions.
Instances of Monad
should satisfy the following laws:
Furthermore, the Monad
and Applicative
operations should relate as follows:
The above laws imply:
and that pure
and (<*>
) satisfy the applicative functor laws.
The instances of Monad
for lists, Maybe
and IO
defined in the Prelude satisfy these laws.
Minimal complete definition
Methods
(>>=) :: m a -> (a -> m b) -> m b infixl 1 #
Sequentially compose two actions, passing any value produced by the first as an argument to the second.
(>>) :: m a -> m b -> m b infixl 1 #
Sequentially compose two actions, discarding any value produced by the first, like sequencing operators (such as the semicolon) in imperative languages.
Inject a value into the monadic type.
Fail with a message. This operation is not part of the
mathematical definition of a monad, but is invoked on pattern-match
failure in a do
expression.
As part of the MonadFail proposal (MFP), this function is moved
to its own class MonadFail
(see Control.Monad.Fail for more
details). The definition here will be removed in a future
release.
Instances
Monad [] | Since: base-2.1 |
Monad Maybe | Since: base-2.1 |
Monad IO | Since: base-2.1 |
Monad Par1 | Since: base-4.9.0.0 |
Monad Q | |
Monad Rose | |
Monad Gen | |
Monad IResult | |
Monad Result | |
Monad Parser | |
Monad Complex | Since: base-4.9.0.0 |
Monad Min | Since: base-4.9.0.0 |
Monad Max | Since: base-4.9.0.0 |
Monad First | Since: base-4.9.0.0 |
Monad Last | Since: base-4.9.0.0 |
Monad Option | Since: base-4.9.0.0 |
Monad Identity | Since: base-4.8.0.0 |
Monad STM | Since: base-4.3.0.0 |
Monad First | Since: base-4.8.0.0 |
Monad Last | Since: base-4.8.0.0 |
Monad Dual | Since: base-4.8.0.0 |
Monad Sum | Since: base-4.8.0.0 |
Monad Product | Since: base-4.8.0.0 |
Monad Down | Since: base-4.11.0.0 |
Monad ReadP | Since: base-2.1 |
Monad NonEmpty | Since: base-4.9.0.0 |
Monad PutM | |
Monad Tree | |
Monad Seq | |
Monad Criterion | |
Monad DList | |
Monad Root | |
Monad SmallArray | |
Defined in Data.Primitive.SmallArray Methods (>>=) :: SmallArray a -> (a -> SmallArray b) -> SmallArray b # (>>) :: SmallArray a -> SmallArray b -> SmallArray b # return :: a -> SmallArray a # fail :: String -> SmallArray a # | |
Monad Array | |
Monad Get | |
Monad Vector | |
Monad Id | |
Monad Box | |
Monad P | Since: base-2.1 |
() :=> (Monad ((->) a :: Type -> Type)) | |
Defined in Data.Constraint | |
() :=> (Monad []) | |
Defined in Data.Constraint | |
() :=> (Monad IO) | |
() :=> (Monad (Either a)) | |
() :=> (Monad Identity) | |
Monad (Either e) | Since: base-4.4.0.0 |
Monad (U1 :: Type -> Type) | Since: base-4.9.0.0 |
Monoid a => Monad ((,) a) | Since: base-4.9.0.0 |
Monad (ST s) | Since: base-2.1 |
Monad m => Monad (PropertyM m) | |
Monad (Parser i) | |
Monad m => Monad (WrappedMonad m) | Since: base-4.7.0.0 |
Defined in Control.Applicative Methods (>>=) :: WrappedMonad m a -> (a -> WrappedMonad m b) -> WrappedMonad m b # (>>) :: WrappedMonad m a -> WrappedMonad m b -> WrappedMonad m b # return :: a -> WrappedMonad m a # fail :: String -> WrappedMonad m a # | |
ArrowApply a => Monad (ArrowMonad a) | Since: base-2.1 |
Defined in Control.Arrow Methods (>>=) :: ArrowMonad a a0 -> (a0 -> ArrowMonad a b) -> ArrowMonad a b # (>>) :: ArrowMonad a a0 -> ArrowMonad a b -> ArrowMonad a b # return :: a0 -> ArrowMonad a a0 # fail :: String -> ArrowMonad a a0 # | |
Monad (Proxy :: Type -> Type) | Since: base-4.7.0.0 |
Monad m => Monad (MaybeT m) | |
Monad m => Monad (ListT m) | |
Monad q => Monad (DsM q) | |
Monad (SetM s) | |
Class (Applicative f) (Monad f) | |
Defined in Data.Constraint Methods cls :: Monad f :- Applicative f # | |
(Monad m) :=> (Functor (WrappedMonad m)) | |
Defined in Data.Constraint | |
(Monad m) :=> (Applicative (WrappedMonad m)) | |
Defined in Data.Constraint Methods ins :: Monad m :- Applicative (WrappedMonad m) # | |
Monad f => Monad (Rec1 f) | Since: base-4.9.0.0 |
Monad m => Monad (RandT g m) | |
Monad f => Monad (Ap f) | Since: base-4.12.0.0 |
Monad f => Monad (Alt f) | Since: base-4.8.0.0 |
Monad m => Monad (IdentityT m) | |
(Applicative f, Monad f) => Monad (WhenMissing f x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal Methods (>>=) :: WhenMissing f x a -> (a -> WhenMissing f x b) -> WhenMissing f x b # (>>) :: WhenMissing f x a -> WhenMissing f x b -> WhenMissing f x b # return :: a -> WhenMissing f x a # fail :: String -> WhenMissing f x a # | |
Monad m => Monad (ExceptT e m) | |
(Monad m, Error e) => Monad (ErrorT e m) | |
Monad m => Monad (StateT s m) | |
Monad m => Monad (StateT s m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
(Monoid w, Monad m) => Monad (WriterT w m) | |
Monad (Tagged s) | |
(Monoid w, Functor m, Monad m) => Monad (AccumT w m) | |
Monad m => Monad (SelectT r m) | |
Class (Monad f, Alternative f) (MonadPlus f) | |
Defined in Data.Constraint | |
Monad ((->) r :: Type -> Type) | Since: base-2.1 |
(Monad f, Monad g) => Monad (f :*: g) | Since: base-4.9.0.0 |
(Monad f, Monad g) => Monad (Product f g) | Since: base-4.9.0.0 |
(Monad f, Applicative f) => Monad (WhenMatched f x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.IntMap.Internal Methods (>>=) :: WhenMatched f x y a -> (a -> WhenMatched f x y b) -> WhenMatched f x y b # (>>) :: WhenMatched f x y a -> WhenMatched f x y b -> WhenMatched f x y b # return :: a -> WhenMatched f x y a # fail :: String -> WhenMatched f x y a # | |
(Applicative f, Monad f) => Monad (WhenMissing f k x) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal Methods (>>=) :: WhenMissing f k x a -> (a -> WhenMissing f k x b) -> WhenMissing f k x b # (>>) :: WhenMissing f k x a -> WhenMissing f k x b -> WhenMissing f k x b # return :: a -> WhenMissing f k x a # fail :: String -> WhenMissing f k x a # | |
Monad m => Monad (CRandT g e m) | |
Monad (ContT r m) | |
Monad m => Monad (ReaderT r m) | |
Monad (ParsecT s u m) | |
Monad f => Monad (M1 i c f) | Since: base-4.9.0.0 |
(Monad f, Applicative f) => Monad (WhenMatched f k x y) | Equivalent to Since: containers-0.5.9 |
Defined in Data.Map.Internal Methods (>>=) :: WhenMatched f k x y a -> (a -> WhenMatched f k x y b) -> WhenMatched f k x y b # (>>) :: WhenMatched f k x y a -> WhenMatched f k x y b -> WhenMatched f k x y b # return :: a -> WhenMatched f k x y a # fail :: String -> WhenMatched f k x y a # | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
(Monoid w, Monad m) => Monad (RWST r w s m) | |
Monad m => Monad (TaggedT s m) | |
class Functor (f :: Type -> Type) where #
The Functor
class is used for types that can be mapped over.
Instances of Functor
should satisfy the following laws:
fmap id == id fmap (f . g) == fmap f . fmap g
The instances of Functor
for lists, Maybe
and IO
satisfy these laws.
Minimal complete definition
Instances
The Ord
class is used for totally ordered datatypes.
Instances of Ord
can be derived for any user-defined datatype whose
constituent types are in Ord
. The declared order of the constructors in
the data declaration determines the ordering in derived Ord
instances. The
Ordering
datatype allows a single comparison to determine the precise
ordering of two objects.
The Haskell Report defines no laws for Ord
. However, <=
is customarily
expected to implement a non-strict partial order and have the following
properties:
- Transitivity
- if
x <= y && y <= z
=True
, thenx <= z
=True
- Reflexivity
x <= x
=True
- Antisymmetry
- if
x <= y && y <= x
=True
, thenx == y
=True
Note that the following operator interactions are expected to hold:
x >= y
=y <= x
x < y
=x <= y && x /= y
x > y
=y < x
x < y
=compare x y == LT
x > y
=compare x y == GT
x == y
=compare x y == EQ
min x y == if x <= y then x else y
=True
max x y == if x >= y then x else y
=True
Minimal complete definition: either compare
or <=
.
Using compare
can be more efficient for complex types.
Methods
compare :: a -> a -> Ordering #
(<) :: a -> a -> Bool infix 4 #
(<=) :: a -> a -> Bool infix 4 #
Instances
Parsing of String
s, producing values.
Derived instances of Read
make the following assumptions, which
derived instances of Show
obey:
- If the constructor is defined to be an infix operator, then the
derived
Read
instance will parse only infix applications of the constructor (not the prefix form). - Associativity is not used to reduce the occurrence of parentheses, although precedence may be.
- If the constructor is defined using record syntax, the derived
Read
will parse only the record-syntax form, and furthermore, the fields must be given in the same order as the original declaration. - The derived
Read
instance allows arbitrary Haskell whitespace between tokens of the input string. Extra parentheses are also allowed.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Read
in Haskell 2010 is equivalent to
instance (Read a) => Read (Tree a) where readsPrec d r = readParen (d > app_prec) (\r -> [(Leaf m,t) | ("Leaf",s) <- lex r, (m,t) <- readsPrec (app_prec+1) s]) r ++ readParen (d > up_prec) (\r -> [(u:^:v,w) | (u,s) <- readsPrec (up_prec+1) r, (":^:",t) <- lex s, (v,w) <- readsPrec (up_prec+1) t]) r where app_prec = 10 up_prec = 5
Note that right-associativity of :^:
is unused.
The derived instance in GHC is equivalent to
instance (Read a) => Read (Tree a) where readPrec = parens $ (prec app_prec $ do Ident "Leaf" <- lexP m <- step readPrec return (Leaf m)) +++ (prec up_prec $ do u <- step readPrec Symbol ":^:" <- lexP v <- step readPrec return (u :^: v)) where app_prec = 10 up_prec = 5 readListPrec = readListPrecDefault
Why do both readsPrec
and readPrec
exist, and why does GHC opt to
implement readPrec
in derived Read
instances instead of readsPrec
?
The reason is that readsPrec
is based on the ReadS
type, and although
ReadS
is mentioned in the Haskell 2010 Report, it is not a very efficient
parser data structure.
readPrec
, on the other hand, is based on a much more efficient ReadPrec
datatype (a.k.a "new-style parsers"), but its definition relies on the use
of the RankNTypes
language extension. Therefore, readPrec
(and its
cousin, readListPrec
) are marked as GHC-only. Nevertheless, it is
recommended to use readPrec
instead of readsPrec
whenever possible
for the efficiency improvements it brings.
As mentioned above, derived Read
instances in GHC will implement
readPrec
instead of readsPrec
. The default implementations of
readsPrec
(and its cousin, readList
) will simply use readPrec
under
the hood. If you are writing a Read
instance by hand, it is recommended
to write it like so:
instanceRead
T wherereadPrec
= ...readListPrec
=readListPrecDefault
Methods
Arguments
:: Int | the operator precedence of the enclosing
context (a number from |
-> ReadS a |
attempts to parse a value from the front of the string, returning a list of (parsed value, remaining string) pairs. If there is no successful parse, the returned list is empty.
Derived instances of Read
and Show
satisfy the following:
That is, readsPrec
parses the string produced by
showsPrec
, and delivers the value that
showsPrec
started with.
Instances
Conversion of values to readable String
s.
Derived instances of Show
have the following properties, which
are compatible with derived instances of Read
:
- The result of
show
is a syntactically correct Haskell expression containing only constants, given the fixity declarations in force at the point where the type is declared. It contains only the constructor names defined in the data type, parentheses, and spaces. When labelled constructor fields are used, braces, commas, field names, and equal signs are also used. - If the constructor is defined to be an infix operator, then
showsPrec
will produce infix applications of the constructor. - the representation will be enclosed in parentheses if the
precedence of the top-level constructor in
x
is less thand
(associativity is ignored). Thus, ifd
is0
then the result is never surrounded in parentheses; ifd
is11
it is always surrounded in parentheses, unless it is an atomic expression. - If the constructor is defined using record syntax, then
show
will produce the record-syntax form, with the fields given in the same order as the original declaration.
For example, given the declarations
infixr 5 :^: data Tree a = Leaf a | Tree a :^: Tree a
the derived instance of Show
is equivalent to
instance (Show a) => Show (Tree a) where showsPrec d (Leaf m) = showParen (d > app_prec) $ showString "Leaf " . showsPrec (app_prec+1) m where app_prec = 10 showsPrec d (u :^: v) = showParen (d > up_prec) $ showsPrec (up_prec+1) u . showString " :^: " . showsPrec (up_prec+1) v where up_prec = 5
Note that right-associativity of :^:
is ignored. For example,
produces the stringshow
(Leaf 1 :^: Leaf 2 :^: Leaf 3)"Leaf 1 :^: (Leaf 2 :^: Leaf 3)"
.
Methods
Arguments
:: Int | the operator precedence of the enclosing
context (a number from |
-> a | the value to be converted to a |
-> ShowS |
Convert a value to a readable String
.
showsPrec
should satisfy the law
showsPrec d x r ++ s == showsPrec d x (r ++ s)
Derived instances of Read
and Show
satisfy the following:
That is, readsPrec
parses the string produced by
showsPrec
, and delivers the value that showsPrec
started with.
Instances
foldr :: Foldable t => (a -> b -> b) -> b -> t a -> b #
Right-associative fold of a structure.
In the case of lists, foldr
, when applied to a binary operator, a
starting value (typically the right-identity of the operator), and a
list, reduces the list using the binary operator, from right to left:
foldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)
Note that, since the head of the resulting expression is produced by
an application of the operator to the first element of the list,
foldr
can produce a terminating expression from an infinite list.
For a general Foldable
structure this should be semantically identical
to,
foldr f z =foldr
f z .toList
length :: Foldable t => t a -> Int #
Returns the size/length of a finite structure as an Int
. The
default implementation is optimized for structures that are similar to
cons-lists, because there is no general way to do better.
null :: Foldable t => t a -> Bool #
Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.
foldl :: Foldable t => (b -> a -> b) -> b -> t a -> b #
Left-associative fold of a structure.
In the case of lists, foldl
, when applied to a binary
operator, a starting value (typically the left-identity of the operator),
and a list, reduces the list using the binary operator, from left to
right:
foldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn
Note that to produce the outermost application of the operator the
entire input list must be traversed. This means that foldl'
will
diverge if given an infinite list.
Also note that if you want an efficient left-fold, you probably want to
use foldl'
instead of foldl
. The reason for this is that latter does
not force the "inner" results (e.g. z
in the above example)
before applying them to the operator (e.g. to f
x1(
). This results
in a thunk chain f
x2)O(n)
elements long, which then must be evaluated from
the outside-in.
For a general Foldable
structure this should be semantically identical
to,
foldl f z =foldl
f z .toList
mapM :: (Traversable t, Monad m) => (a -> m b) -> t a -> m (t b) #
Map each element of a structure to a monadic action, evaluate
these actions from left to right, and collect the results. For
a version that ignores the results see mapM_
.
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) #
Evaluate each monadic action in the structure from left to
right, and collect the results. For a version that ignores the
results see sequence_
.
Instances
Bounded Bool | Since: base-2.1 |
Enum Bool | Since: base-2.1 |
Eq Bool | |
Data Bool | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bool -> c Bool # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bool # dataTypeOf :: Bool -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bool) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bool) # gmapT :: (forall b. Data b => b -> b) -> Bool -> Bool # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bool -> r # gmapQ :: (forall d. Data d => d -> u) -> Bool -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bool -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bool -> m Bool # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bool -> m Bool # | |
Ord Bool | |
Read Bool | Since: base-2.1 |
Show Bool | Since: base-2.1 |
Ix Bool | Since: base-2.1 |
Generic Bool | |
Lift Bool | |
Random Bool | |
Testable Bool | |
NFData Bool | |
Defined in Control.DeepSeq | |
Hashable Bool | |
Defined in Data.Hashable.Class | |
ToJSON Bool | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey Bool | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON Bool | |
FromJSONKey Bool | |
Defined in Data.Aeson.Types.FromJSON | |
SingKind Bool | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Storable Bool | Since: base-2.1 |
Defined in Foreign.Storable | |
Default Bool Source # | |
Defined in Crypto.Lol.Prelude | |
CRandom Bool | |
Defined in Control.Monad.CryptoRandom Methods crandom :: CryptoRandomGen g => g -> Either GenError (Bool, g) # crandoms :: CryptoRandomGen g => g -> [Bool] # | |
Variate Bool | |
GPB Bool | |
Defined in Text.ProtocolBuffers.Extensions | |
Wire Bool | |
TextType Bool | |
Mergeable Bool | |
Defined in Text.ProtocolBuffers.Basic | |
Default Bool | |
Defined in Text.ProtocolBuffers.Basic Methods defaultValue :: Bool # | |
PShow Bool | |
SShow Bool | |
PEnum Bool | |
Defined in Data.Singletons.Prelude.Enum | |
SEnum Bool | |
Defined in Data.Singletons.Prelude.Enum Methods sSucc :: Sing t -> Sing (Apply SuccSym0 t) # sPred :: Sing t -> Sing (Apply PredSym0 t) # sToEnum :: Sing t -> Sing (Apply ToEnumSym0 t) # sFromEnum :: Sing t -> Sing (Apply FromEnumSym0 t) # sEnumFromTo :: Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) # sEnumFromThenTo :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) # | |
PBounded Bool | |
Defined in Data.Singletons.Prelude.Enum | |
SBounded Bool | |
Defined in Data.Singletons.Prelude.Enum | |
POrd Bool | |
SOrd Bool | |
Defined in Data.Singletons.Prelude.Ord Methods sCompare :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) # (%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) # (%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) # (%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) # (%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) # sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) # sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) # | |
SEq Bool | |
PEq Bool | |
Unbox Bool | |
Defined in Data.Vector.Unboxed.Base | |
SingI False | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
SingI True | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Vector Vector Bool | |
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) Bool -> m (Vector Bool) # basicUnsafeThaw :: PrimMonad m => Vector Bool -> m (Mutable Vector (PrimState m) Bool) # basicLength :: Vector Bool -> Int # basicUnsafeSlice :: Int -> Int -> Vector Bool -> Vector Bool # basicUnsafeIndexM :: Monad m => Vector Bool -> Int -> m Bool # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) Bool -> Vector Bool -> m () # | |
MVector MVector Bool | |
Defined in Data.Vector.Unboxed.Base Methods basicLength :: MVector s Bool -> Int # basicUnsafeSlice :: Int -> Int -> MVector s Bool -> MVector s Bool # basicOverlaps :: MVector s Bool -> MVector s Bool -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) Bool) # basicInitialize :: PrimMonad m => MVector (PrimState m) Bool -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Bool -> m (MVector (PrimState m) Bool) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) Bool -> Int -> m Bool # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) Bool -> Int -> Bool -> m () # basicClear :: PrimMonad m => MVector (PrimState m) Bool -> m () # basicSet :: PrimMonad m => MVector (PrimState m) Bool -> Bool -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) Bool -> MVector (PrimState m) Bool -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) Bool -> MVector (PrimState m) Bool -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) Bool -> Int -> m (MVector (PrimState m) Bool) # | |
() :=> (Bounded Bool) | |
() :=> (Enum Bool) | |
() :=> (Eq Bool) | |
() :=> (Ord Bool) | |
() :=> (Read Bool) | |
() :=> (Show Bool) | |
() :=> (Bits Bool) | |
SuppressUnusedWarnings NotSym0 | |
Defined in Data.Singletons.Prelude.Bool Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings FromEnum_6989586621679763764Sym0 | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings AllSym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings All_Sym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings AnySym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Any_Sym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (||@#@$) | |
Defined in Data.Singletons.Prelude.Bool Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (&&@#@$) | |
Defined in Data.Singletons.Prelude.Bool Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Compare_6989586621679391374Sym0 | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowParenSym0 | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings OrSym0 | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings AndSym0 | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ToEnum_6989586621679763758Sym0 | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680280967Sym0 | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (<=?@#@$) | |
Defined in Data.Singletons.TypeLits.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings GetAllSym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings GetAnySym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SingI NotSym0 | |
Defined in Data.Singletons.Prelude.Bool | |
SingI (||@#@$) | |
Defined in Data.Singletons.Prelude.Bool | |
SingI (&&@#@$) | |
Defined in Data.Singletons.Prelude.Bool | |
SingI (<=?@#@$) | |
Defined in Data.Singletons.TypeLits.Internal | |
SingI AllSym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
SingI AnySym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
SingI ShowParenSym0 | |
Defined in Data.Singletons.Prelude.Show Methods sing :: Sing ShowParenSym0 # | |
SingI OrSym0 | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI AndSym0 | |
Defined in Data.Singletons.Prelude.List.Internal | |
SuppressUnusedWarnings ((||@#@$$) a6989586621679360668 :: TyFun Bool Bool -> Type) | |
Defined in Data.Singletons.Prelude.Bool Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((&&@#@$$) a6989586621679360427 :: TyFun Bool Bool -> Type) | |
Defined in Data.Singletons.Prelude.Bool Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391374Sym1 a6989586621679391372 :: TyFun Bool Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (GuardSym0 :: TyFun Bool (f6989586621679544591 ()) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680280967Sym1 a6989586621680280964 :: TyFun Bool (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (WhenSym0 :: TyFun Bool (f6989586621679544620 () ~> f6989586621679544620 ()) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (UnlessSym0 :: TyFun Bool (f6989586621681207764 () ~> f6989586621681207764 ()) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListnullSym0 :: TyFun [a6989586621680387251] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListisPrefixOfSym0 :: TyFun [a6989586621680387274] ([a6989586621680387274] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (NullSym0 :: TyFun [a6989586621679939789] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a6989586621679939754] ([a6989586621679939754] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a6989586621679939755] ([a6989586621679939755] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a6989586621679939753] ([a6989586621679939753] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a6989586621679495146) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679495147) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((<=?@#@$$) a3530822107858468865 :: TyFun Nat Bool -> Type) | |
Defined in Data.Singletons.TypeLits.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListelemSym0 :: TyFun a6989586621680387262 ([a6989586621680387262] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621679939751 ([a6989586621679939751] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621679939752 ([a6989586621679939752] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (OrSym0 :: TyFun (t6989586621680450647 Bool) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451216Scrutinee_6989586621680450974Sym0 :: TyFun (t6989586621680450727 Bool) All -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451207Scrutinee_6989586621680450976Sym0 :: TyFun (t6989586621680450727 Bool) Any -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442550Scrutinee_6989586621680442488Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442523Scrutinee_6989586621680442486Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AndSym0 :: TyFun (t6989586621680450648 Bool) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Bool_Sym0 :: TyFun a6989586621679359676 (a6989586621679359676 ~> (Bool ~> a6989586621679359676)) -> Type) | |
Defined in Data.Singletons.Prelude.Bool Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (DefaultEqSym0 :: TyFun k6989586621679363690 (k6989586621679363690 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Eq Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((==@#@$) :: TyFun a6989586621679363696 (a6989586621679363696 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Eq Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((/=@#@$) :: TyFun a6989586621679363696 (a6989586621679363696 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Eq Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679380186Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679380168Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679380150Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679380132Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380214Scrutinee_6989586621679380009Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380196Scrutinee_6989586621679380007Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380105Scrutinee_6989586621679379997Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380100Scrutinee_6989586621679379995Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((>@#@$) :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((>=@#@$) :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((<@#@$) :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((<=@#@$) :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680676101Sym0 :: TyFun a6989586621680450744 (Identity a6989586621680450744 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Identity Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Null_6989586621680676224Sym0 :: TyFun (Identity a6989586621680450742) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Identity Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListtakeWhileSym0 :: TyFun (a6989586621680387280 ~> Bool) ([a6989586621680387280] ~> [a6989586621680387280]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListspanSym0 :: TyFun (a6989586621680387278 ~> Bool) ([a6989586621680387278] ~> ([a6989586621680387278], [a6989586621680387278])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListpartitionSym0 :: TyFun (a6989586621680387276 ~> Bool) ([a6989586621680387276] ~> ([a6989586621680387276], [a6989586621680387276])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListnubBySym0 :: TyFun (a6989586621680387268 ~> (a6989586621680387268 ~> Bool)) ([a6989586621680387268] ~> [a6989586621680387268]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListfilterSym0 :: TyFun (a6989586621680387277 ~> Bool) ([a6989586621680387277] ~> [a6989586621680387277]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListdropWhileSym0 :: TyFun (a6989586621680387279 ~> Bool) ([a6989586621680387279] ~> [a6989586621680387279]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (UnionBySym0 :: TyFun (a6989586621679939668 ~> (a6989586621679939668 ~> Bool)) ([a6989586621679939668] ~> ([a6989586621679939668] ~> [a6989586621679939668])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a6989586621679939695 ~> Bool) ([a6989586621679939695] ~> [a6989586621679939695]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (SpanSym0 :: TyFun (a6989586621679939692 ~> Bool) ([a6989586621679939692] ~> ([a6989586621679939692], [a6989586621679939692])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (SelectSym0 :: TyFun (a6989586621679939678 ~> Bool) (a6989586621679939678 ~> (([a6989586621679939678], [a6989586621679939678]) ~> ([a6989586621679939678], [a6989586621679939678]))) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (PartitionSym0 :: TyFun (a6989586621679939679 ~> Bool) ([a6989586621679939679] ~> ([a6989586621679939679], [a6989586621679939679])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (NubBySym0 :: TyFun (a6989586621679939670 ~> (a6989586621679939670 ~> Bool)) ([a6989586621679939670] ~> [a6989586621679939670]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949153ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949153YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949153X_6989586621679949154Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949110ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949110YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949110X_6989586621679949111Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a6989586621679939696 ~> (a6989586621679939696 ~> Bool)) ([a6989586621679939696] ~> ([a6989586621679939696] ~> [a6989586621679939696])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (GroupBySym0 :: TyFun (a6989586621679939682 ~> (a6989586621679939682 ~> Bool)) ([a6989586621679939682] ~> [[a6989586621679939682]]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621679939702 ~> Bool) ([a6989586621679939702] ~> Maybe a6989586621679939702) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a6989586621679939698 ~> Bool) ([a6989586621679939698] ~> [Nat]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a6989586621679939699 ~> Bool) ([a6989586621679939699] ~> Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FilterSym0 :: TyFun (a6989586621679939703 ~> Bool) ([a6989586621679939703] ~> [a6989586621679939703]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_bySym0 :: TyFun (a6989586621679939669 ~> (a6989586621679939669 ~> Bool)) (a6989586621679939669 ~> ([a6989586621679939669] ~> Bool)) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a6989586621679939694 ~> Bool) ([a6989586621679939694] ~> [a6989586621679939694]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a6989586621679939693 ~> Bool) ([a6989586621679939693] ~> [a6989586621679939693]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a6989586621679939708 ~> (a6989586621679939708 ~> Bool)) ([a6989586621679939708] ~> ([a6989586621679939708] ~> [a6989586621679939708])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a6989586621679939709 ~> (a6989586621679939709 ~> Bool)) (a6989586621679939709 ~> ([a6989586621679939709] ~> [a6989586621679939709])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (BreakSym0 :: TyFun (a6989586621679939691 ~> Bool) ([a6989586621679939691] ~> ([a6989586621679939691], [a6989586621679939691])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621679939772 ~> Bool) ([a6989586621679939772] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621679939773 ~> Bool) ([a6989586621679939773] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (UntilSym0 :: TyFun (a6989586621679520379 ~> Bool) ((a6989586621679520379 ~> a6989586621679520379) ~> (a6989586621679520379 ~> a6989586621679520379)) -> Type) | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () # | |
SingI x => SingI ((||@#@$$) x :: TyFun Bool Bool -> Type) | |
Defined in Data.Singletons.Prelude.Bool | |
SingI x => SingI ((&&@#@$$) x :: TyFun Bool Bool -> Type) | |
Defined in Data.Singletons.Prelude.Bool | |
SingI x => SingI ((<=?@#@$$) x :: TyFun Nat Bool -> Type) | |
Defined in Data.Singletons.TypeLits.Internal Methods sing :: Sing ((<=?@#@$$) x) # | |
SAlternative f => SingI (GuardSym0 :: TyFun Bool (f ()) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
SApplicative f => SingI (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
SApplicative f => SingI (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods sing :: Sing UnlessSym0 # | |
SingI (ListnullSym0 :: TyFun [a] Bool -> Type) | |
SEq a => SingI (ListisPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) | |
SingI (NullSym0 :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing IsSuffixOfSym0 # | |
SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing IsPrefixOfSym0 # | |
SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing IsInfixOfSym0 # | |
SingI (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing IsNothingSym0 # | |
SingI (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing IsJustSym0 # | |
SEq a => SingI (ListelemSym0 :: TyFun a ([a] ~> Bool) -> Type) | |
SEq a => SingI (NotElemSym0 :: TyFun a ([a] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SEq a => SingI (ElemSym0 :: TyFun a ([a] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SingI (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) | |
Defined in Data.Singletons.Prelude.Bool | |
SEq a => SingI ((==@#@$) :: TyFun a (a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Eq | |
SEq a => SingI ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Eq | |
SOrd a => SingI ((>@#@$) :: TyFun a (a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord | |
SOrd a => SingI ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord | |
SOrd a => SingI ((<@#@$) :: TyFun a (a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord | |
SOrd a => SingI ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Ord | |
SingI (ListtakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) | |
SingI (ListspanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) | |
SingI (ListpartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) | |
SingI (ListnubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) | |
SingI (ListfilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) | |
SingI (ListdropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) | |
SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnionBySym0 # | |
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing TakeWhileSym0 # | |
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (SelectSym0 :: TyFun (a ~> Bool) (a ~> (([a], [a]) ~> ([a], [a]))) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing PartitionSym0 # | |
SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing IntersectBySym0 # | |
SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing GroupBySym0 # | |
SingI (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Nat]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing FindIndicesSym0 # | |
SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing FindIndexSym0 # | |
SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing FilterSym0 # | |
SingI (Elem_bySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> Bool)) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing DropWhileSym0 # | |
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods | |
SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing DeleteBySym0 # | |
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (AnySym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (AllSym0 :: TyFun (a ~> Bool) ([a] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) | |
Defined in Data.Singletons.Prelude.Base | |
SuppressUnusedWarnings (ListisPrefixOfSym1 a6989586621680388326 :: TyFun [a6989586621680387274] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListelemSym1 a6989586621680388261 :: TyFun [a6989586621680387262] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (NotElemSym1 a6989586621679949635 :: TyFun [a6989586621679939751] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679950260 :: TyFun [a6989586621679939754] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679949669 :: TyFun [a6989586621679939755] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679949907 :: TyFun [a6989586621679939753] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ElemSym1 a6989586621679949642 :: TyFun [a6989586621679939752] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AnySym1 a6989586621679949900 :: TyFun [a6989586621679939772] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AllSym1 a6989586621679949955 :: TyFun [a6989586621679939773] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621680432173 b6989586621680432174) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621680432175 b6989586621680432176) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948982Scrutinee_6989586621679940370Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_bySym1 a6989586621679948927 :: TyFun a6989586621679939669 ([a6989586621679939669] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (NotElemSym0 :: TyFun a6989586621680450638 (t6989586621680450637 a6989586621680450638 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442550Scrutinee_6989586621680442488Sym1 x6989586621680442543 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442523Scrutinee_6989586621680442486Sym1 x6989586621680442516 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680452447Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680452280Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680452113Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680451776Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680451653Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ElemSym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Bool_Sym1 a6989586621679359682 :: TyFun a6989586621679359676 (Bool ~> a6989586621679359676) -> Type) | |
Defined in Data.Singletons.Prelude.Bool Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (DefaultEqSym1 a6989586621679363691 :: TyFun k6989586621679363690 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Eq Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((==@#@$$) x6989586621679363697 :: TyFun a6989586621679363696 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Eq Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((/=@#@$$) x6989586621679363699 :: TyFun a6989586621679363696 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Eq Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679380186Sym1 a6989586621679380184 :: TyFun a6989586621679379977 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679380168Sym1 a6989586621679380166 :: TyFun a6989586621679379977 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679380150Sym1 a6989586621679380148 :: TyFun a6989586621679379977 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679380132Sym1 a6989586621679380130 :: TyFun a6989586621679379977 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380214Scrutinee_6989586621679380009Sym1 x6989586621679380212 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380196Scrutinee_6989586621679380007Sym1 x6989586621679380194 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380105Scrutinee_6989586621679379997Sym1 x6989586621679380098 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380100Scrutinee_6989586621679379995Sym1 x6989586621679380098 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((>@#@$$) arg6989586621679380078 :: TyFun a6989586621679379977 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((>=@#@$$) arg6989586621679380082 :: TyFun a6989586621679379977 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((<@#@$$) arg6989586621679380070 :: TyFun a6989586621679379977 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ((<=@#@$$) arg6989586621679380074 :: TyFun a6989586621679379977 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621680882853Sym0 :: TyFun (Arg a6989586621680881636 b6989586621680881637) (Arg a6989586621680881636 b6989586621680881637 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680676101Sym1 a6989586621680676099 :: TyFun (Identity a6989586621680450744) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Identity Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949185ZsSym0 :: TyFun (k1 ~> (a6989586621679939692 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939692] [a6989586621679939692] -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949185YsSym0 :: TyFun (k1 ~> (a6989586621679939692 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939692] [a6989586621679939692] -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949185X_6989586621679949186Sym0 :: TyFun (k1 ~> (a6989586621679939692 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939692] ([a6989586621679939692], [a6989586621679939692]) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948943NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621679950276Sym0 :: TyFun (a6989586621679939789 ~> Bool) (TyFun k (TyFun a6989586621679939789 (TyFun [a6989586621679939789] [a6989586621679939789] -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451197Scrutinee_6989586621680450978Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) Any -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451184Scrutinee_6989586621680450980Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) All -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451099Scrutinee_6989586621680450986Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) (First a6989586621680450730) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680451100Sym0 :: TyFun (a6989586621679072651 ~> Bool) (TyFun k (TyFun a6989586621679072651 (First a6989586621679072651) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680450636 ~> Bool) (t6989586621680450635 a6989586621680450636 ~> Maybe a6989586621680450636) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AnySym0 :: TyFun (a6989586621680450646 ~> Bool) (t6989586621680450645 a6989586621680450646 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AllSym0 :: TyFun (a6989586621680450644 ~> Bool) (t6989586621680450643 a6989586621680450644 ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679520515GoSym0 :: TyFun (k2 ~> Bool) (TyFun (k2 ~> k2) (TyFun k1 (TyFun k2 k2 -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Base Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MfilterSym0 :: TyFun (a6989586621681207760 ~> Bool) (m6989586621681207759 a6989586621681207760 ~> m6989586621681207759 a6989586621681207760) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FilterMSym0 :: TyFun (a6989586621681207798 ~> m6989586621681207797 Bool) ([a6989586621681207798] ~> m6989586621681207797 [a6989586621681207798]) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
(SEq a, SingI d) => SingI (ListisPrefixOfSym1 d :: TyFun [a] Bool -> Type) | |
(SEq a, SingI d) => SingI (ListelemSym1 d :: TyFun [a] Bool -> Type) | |
(SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsSuffixOfSym1 d) # | |
(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsPrefixOfSym1 d) # | |
(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (IsInfixOfSym1 d) # | |
(SEq a, SingI d) => SingI (ElemSym1 d :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI d => SingI (AnySym1 d :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI d => SingI (AllSym1 d :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (IsRightSym0 :: TyFun (Either a b) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods sing :: Sing IsRightSym0 # | |
SingI (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods sing :: Sing IsLeftSym0 # | |
SingI d => SingI (Elem_bySym1 d :: TyFun a ([a] ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing NotElemSym0 # | |
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SingI d => SingI (Bool_Sym1 d :: TyFun a (Bool ~> a) -> Type) | |
Defined in Data.Singletons.Prelude.Bool | |
(SEq a, SingI x) => SingI ((==@#@$$) x :: TyFun a Bool -> Type) | |
Defined in Data.Singletons.Prelude.Eq | |
(SEq a, SingI x) => SingI ((/=@#@$$) x :: TyFun a Bool -> Type) | |
Defined in Data.Singletons.Prelude.Eq | |
(SOrd a, SingI d) => SingI ((>@#@$$) d :: TyFun a Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord | |
(SOrd a, SingI d) => SingI ((>=@#@$$) d :: TyFun a Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord | |
(SOrd a, SingI d) => SingI ((<@#@$$) d :: TyFun a Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord | |
(SOrd a, SingI d) => SingI ((<=@#@$$) d :: TyFun a Bool -> Type) | |
Defined in Data.Singletons.Prelude.Ord | |
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SMonadPlus m => SingI (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods sing :: Sing MfilterSym0 # | |
SApplicative m => SingI (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods sing :: Sing FilterMSym0 # | |
SuppressUnusedWarnings (Bool_Sym2 a6989586621679359683 a6989586621679359682 :: TyFun Bool a6989586621679359676 -> Type) | |
Defined in Data.Singletons.Prelude.Bool Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_bySym2 a6989586621679948928 a6989586621679948927 :: TyFun [a6989586621679939669] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949661Scrutinee_6989586621679940374Sym0 :: TyFun k1 (TyFun k3 (TyFun k2 (TyFun [k3] Bool -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949079Scrutinee_6989586621679940354Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949065Scrutinee_6989586621679940356Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949050Scrutinee_6989586621679940366Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948982Scrutinee_6989586621679940370Sym1 n6989586621679948980 :: TyFun k Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948969Scrutinee_6989586621679940372Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Null_6989586621680452570Sym0 :: TyFun (t6989586621680450727 a6989586621680450742) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Null_6989586621680452403Sym0 :: TyFun (t6989586621680450727 a6989586621680450742) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Null_6989586621680452236Sym0 :: TyFun (t6989586621680450727 a6989586621680450742) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Null_6989586621680452090Sym0 :: TyFun (t6989586621680450727 a6989586621680450742) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Null_6989586621680451914Sym0 :: TyFun (t6989586621680450727 a6989586621680450742) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Null_6989586621680451616Sym0 :: TyFun (t6989586621680450727 a6989586621680450742) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (NullSym0 :: TyFun (t6989586621680450727 a6989586621680450742) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (NotElemSym1 a6989586621680451120 t6989586621680450637 :: TyFun (t6989586621680450637 a6989586621680450638) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680451603Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680452447Sym1 a6989586621680452445 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680452280Sym1 a6989586621680452278 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680452113Sym1 a6989586621680452111 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680451776Sym1 a6989586621680451774 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Elem_6989586621680451653Sym1 a6989586621680451651 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ElemSym1 arg6989586621680451394 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AnySym1 a6989586621680451191 t6989586621680450645 :: TyFun (t6989586621680450645 a6989586621680450646) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (AllSym1 a6989586621680451178 t6989586621680450643 :: TyFun (t6989586621680450643 a6989586621680450644) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621681208272Sym0 :: TyFun k1 (TyFun k3 (TyFun k2 (TyFun Bool (TyFun [k3] [k3] -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621680882853Sym1 a6989586621680882851 :: TyFun (Arg a6989586621680881636 b6989586621680881637) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679950280Scrutinee_6989586621679940348Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948953Scrutinee_6989586621679940376Sym0 :: TyFun (k3 ~> (k3 ~> Bool)) (TyFun k1 (TyFun k3 (TyFun k2 (TyFun [k3] Bool -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621681208269Sym0 :: TyFun (k3 ~> f6989586621679544675 Bool) (TyFun k2 (TyFun k3 (TyFun (f6989586621679544675 [k3]) (f6989586621679544675 [k3]) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621681208101Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m6989586621679544699 k1) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
(SingI d1, SingI d2) => SingI (Bool_Sym2 d1 d2 :: TyFun Bool a -> Type) | |
Defined in Data.Singletons.Prelude.Bool | |
(SingI d1, SingI d2) => SingI (Elem_bySym2 d1 d2 :: TyFun [a] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d t :: TyFun (t a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing (NotElemSym1 d t) # | |
(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d t :: TyFun (t a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
(SFoldable t, SingI d) => SingI (AnySym1 d t :: TyFun (t a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
(SFoldable t, SingI d) => SingI (AllSym1 d t :: TyFun (t a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SuppressUnusedWarnings (Let6989586621679950280Scrutinee_6989586621679940348Sym1 p6989586621679950274 :: TyFun k1 (TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949661Scrutinee_6989586621679940374Sym1 l6989586621679949651 :: TyFun k2 (TyFun k1 (TyFun [k2] Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949079Scrutinee_6989586621679940354Sym1 n6989586621679949076 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949065Scrutinee_6989586621679940356Sym1 n6989586621679949062 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949050Scrutinee_6989586621679940366Sym1 key6989586621679949046 :: TyFun k3 (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948969Scrutinee_6989586621679940372Sym1 x6989586621679948966 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948953Scrutinee_6989586621679940376Sym1 eq6989586621679948941 :: TyFun k1 (TyFun k3 (TyFun k2 (TyFun [k3] Bool -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680451603Sym1 a_69895866216804515986989586621680451602 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740143Scrutinee_6989586621679739909Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621681208272Sym1 p6989586621681208267 :: TyFun k2 (TyFun k1 (TyFun Bool (TyFun [k2] [k2] -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679950280Scrutinee_6989586621679940348Sym2 x6989586621679950278 p6989586621679950274 :: TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949661Scrutinee_6989586621679940374Sym2 x6989586621679949658 l6989586621679949651 :: TyFun k1 (TyFun [k2] Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949079Scrutinee_6989586621679940354Sym2 x6989586621679949077 n6989586621679949076 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949065Scrutinee_6989586621679940356Sym2 x6989586621679949063 n6989586621679949062 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949050Scrutinee_6989586621679940366Sym2 x6989586621679949047 key6989586621679949046 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948969Scrutinee_6989586621679940372Sym2 xs6989586621679948967 x6989586621679948966 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948953Scrutinee_6989586621679940376Sym2 l6989586621679948942 eq6989586621679948941 :: TyFun k3 (TyFun k1 (TyFun [k3] Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680451603Sym2 t6989586621680451610 a_69895866216804515986989586621680451602 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740143Scrutinee_6989586621679739909Sym1 x06989586621679740133 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740066Scrutinee_6989586621679739923Sym0 :: TyFun k2 (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740009Scrutinee_6989586621679739933Sym0 :: TyFun k2 (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621681208272Sym2 x6989586621681208271 p6989586621681208267 :: TyFun k1 (TyFun Bool (TyFun [k2] [k2] -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621679949935Sym0 :: TyFun (b6989586621679544703 ~> (a6989586621679939772 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939772 (TyFun [a6989586621679939772] (TyFun b6989586621679544703 (m6989586621679544699 b6989586621679544703) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621681208272Sym3 a_69895866216812082656989586621681208268 x6989586621681208271 p6989586621681208267 :: TyFun Bool (TyFun [k2] [k2] -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monad Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949661Scrutinee_6989586621679940374Sym3 xs6989586621679949659 x6989586621679949658 l6989586621679949651 :: TyFun [k2] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679950280Scrutinee_6989586621679940348Sym3 xs6989586621679950279 x6989586621679950278 p6989586621679950274 :: TyFun k Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679949050Scrutinee_6989586621679940366Sym3 y6989586621679949048 x6989586621679949047 key6989586621679949046 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948953Scrutinee_6989586621679940376Sym3 y6989586621679948950 l6989586621679948942 eq6989586621679948941 :: TyFun k1 (TyFun [k3] Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740143Scrutinee_6989586621679739909Sym2 y6989586621679740134 x06989586621679740133 :: TyFun k3 (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740066Scrutinee_6989586621679739923Sym1 x16989586621679740061 :: TyFun k1 (TyFun k5 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740009Scrutinee_6989586621679739933Sym1 x16989586621679740004 :: TyFun k1 (TyFun k5 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679948953Scrutinee_6989586621679940376Sym4 ys6989586621679948951 y6989586621679948950 l6989586621679948942 eq6989586621679948941 :: TyFun [k3] Bool -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740143Scrutinee_6989586621679739909Sym3 x6989586621679740142 y6989586621679740134 x06989586621679740133 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740066Scrutinee_6989586621679739923Sym2 x26989586621679740062 x16989586621679740061 :: TyFun k5 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740009Scrutinee_6989586621679739933Sym2 x26989586621679740005 x16989586621679740004 :: TyFun k5 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740143Scrutinee_6989586621679739909Sym4 arg_69895866216797399056989586621679740129 x6989586621679740142 y6989586621679740134 x06989586621679740133 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740066Scrutinee_6989586621679739923Sym3 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740009Scrutinee_6989586621679739933Sym3 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740066Scrutinee_6989586621679739923Sym4 arg_69895866216797399176989586621679740056 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740009Scrutinee_6989586621679739933Sym4 arg_69895866216797399276989586621679739999 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740066Scrutinee_6989586621679739923Sym5 arg_69895866216797399196989586621679740057 arg_69895866216797399176989586621679740056 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679740009Scrutinee_6989586621679739933Sym5 arg_69895866216797399296989586621679740000 arg_69895866216797399276989586621679739999 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k1 Bool -> Type) | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
type Rep Bool | Since: base-4.6.0.0 |
data Sing (a :: Bool) | |
type DemoteRep Bool | |
Defined in GHC.Generics | |
type MaxBound | |
Defined in Data.Singletons.Prelude.Enum type MaxBound = MaxBound_6989586621679735896Sym0 | |
type MinBound | |
Defined in Data.Singletons.Prelude.Enum type MinBound = MinBound_6989586621679735894Sym0 | |
data Sing (a :: Bool) | |
type Demote Bool | |
Defined in Data.Singletons.Prelude.Instances | |
newtype Vector Bool | |
type Show_ (arg :: Bool) | |
type FromEnum (a :: Bool) | |
Defined in Data.Singletons.Prelude.Enum | |
type ToEnum a | |
Defined in Data.Singletons.Prelude.Enum | |
type Pred (arg :: Bool) | |
type Succ (arg :: Bool) | |
newtype MVector s Bool | |
type ShowList (arg1 :: [Bool]) arg2 | |
type EnumFromTo (arg1 :: Bool) (arg2 :: Bool) | |
type Min (arg1 :: Bool) (arg2 :: Bool) | |
type Max (arg1 :: Bool) (arg2 :: Bool) | |
type (arg1 :: Bool) >= (arg2 :: Bool) | |
type (arg1 :: Bool) > (arg2 :: Bool) | |
type (arg1 :: Bool) <= (arg2 :: Bool) | |
type (arg1 :: Bool) < (arg2 :: Bool) | |
type Compare (a1 :: Bool) (a2 :: Bool) | |
type (x :: Bool) /= (y :: Bool) | |
type (a :: Bool) == (b :: Bool) | |
Defined in Data.Singletons.Prelude.Eq | |
type ShowsPrec a1 (a2 :: Bool) a3 | |
type EnumFromThenTo (arg1 :: Bool) (arg2 :: Bool) (arg3 :: Bool) | |
type Apply NotSym0 (a6989586621679360968 :: Bool) | |
Defined in Data.Singletons.Prelude.Bool | |
type Apply ToEnum_6989586621679763758Sym0 (a6989586621679763757 :: Nat) | |
Defined in Data.Singletons.Prelude.Enum | |
type Apply GetAllSym0 (a6989586621679820201 :: All) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply GetAnySym0 (a6989586621679820215 :: Any) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply FromEnum_6989586621679763764Sym0 (a6989586621679763763 :: Bool) | |
Defined in Data.Singletons.Prelude.Enum | |
type Apply All_Sym0 (a6989586621679853055 :: Bool) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply AllSym0 (t6989586621679820204 :: Bool) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply Any_Sym0 (a6989586621679853054 :: Bool) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply AnySym0 (t6989586621679820218 :: Bool) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply ((||@#@$$) a6989586621679360668 :: TyFun Bool Bool -> Type) (b6989586621679360669 :: Bool) | |
type Apply ((&&@#@$$) a6989586621679360427 :: TyFun Bool Bool -> Type) (b6989586621679360428 :: Bool) | |
type Apply ((<=?@#@$$) a3530822107858468865 :: TyFun Nat Bool -> Type) (b3530822107858468866 :: Nat) | |
Defined in Data.Singletons.TypeLits.Internal | |
type Apply (Compare_6989586621679391374Sym1 a6989586621679391372 :: TyFun Bool Ordering -> Type) (a6989586621679391373 :: Bool) | |
type Apply (Let6989586621680442523Scrutinee_6989586621680442486Sym1 x6989586621680442516 :: TyFun k1 Bool -> Type) (y6989586621680442517 :: k1) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Let6989586621680442550Scrutinee_6989586621680442488Sym1 x6989586621680442543 :: TyFun k1 Bool -> Type) (y6989586621680442544 :: k1) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply ((==@#@$$) x6989586621679363697 :: TyFun a Bool -> Type) (y6989586621679363698 :: a) | |
type Apply ((/=@#@$$) x6989586621679363699 :: TyFun a Bool -> Type) (y6989586621679363700 :: a) | |
type Apply (DefaultEqSym1 a6989586621679363691 :: TyFun k Bool -> Type) (b6989586621679363692 :: k) | |
Defined in Data.Singletons.Prelude.Eq | |
type Apply (Let6989586621679380100Scrutinee_6989586621679379995Sym1 x6989586621679380098 :: TyFun k1 Bool -> Type) (y6989586621679380099 :: k1) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (TFHelper_6989586621679380186Sym1 a6989586621679380184 :: TyFun a Bool -> Type) (a6989586621679380185 :: a) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (TFHelper_6989586621679380168Sym1 a6989586621679380166 :: TyFun a Bool -> Type) (a6989586621679380167 :: a) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (TFHelper_6989586621679380150Sym1 a6989586621679380148 :: TyFun a Bool -> Type) (a6989586621679380149 :: a) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (TFHelper_6989586621679380132Sym1 a6989586621679380130 :: TyFun a Bool -> Type) (a6989586621679380131 :: a) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply ((<=@#@$$) arg6989586621679380074 :: TyFun a Bool -> Type) (arg6989586621679380075 :: a) | |
type Apply ((>=@#@$$) arg6989586621679380082 :: TyFun a Bool -> Type) (arg6989586621679380083 :: a) | |
type Apply ((>@#@$$) arg6989586621679380078 :: TyFun a Bool -> Type) (arg6989586621679380079 :: a) | |
type Apply (Let6989586621679380214Scrutinee_6989586621679380009Sym1 x6989586621679380212 :: TyFun k1 Bool -> Type) (y6989586621679380213 :: k1) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Let6989586621679380196Scrutinee_6989586621679380007Sym1 x6989586621679380194 :: TyFun k1 Bool -> Type) (y6989586621679380195 :: k1) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Let6989586621679380105Scrutinee_6989586621679379997Sym1 x6989586621679380098 :: TyFun k1 Bool -> Type) (y6989586621679380099 :: k1) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply ((<@#@$$) arg6989586621679380070 :: TyFun a Bool -> Type) (arg6989586621679380071 :: a) | |
type Apply (Let6989586621679948982Scrutinee_6989586621679940370Sym1 n6989586621679948980 :: TyFun k Bool -> Type) (x6989586621679948981 :: k) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Bool_Sym2 a6989586621679359683 a6989586621679359682 :: TyFun Bool a -> Type) (a6989586621679359684 :: Bool) | |
type Apply (Let6989586621679948969Scrutinee_6989586621679940372Sym2 xs6989586621679948967 x6989586621679948966 :: TyFun k3 Bool -> Type) (n6989586621679948968 :: k3) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949065Scrutinee_6989586621679940356Sym2 x6989586621679949063 n6989586621679949062 :: TyFun k3 Bool -> Type) (xs6989586621679949064 :: k3) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949079Scrutinee_6989586621679940354Sym2 x6989586621679949077 n6989586621679949076 :: TyFun k3 Bool -> Type) (xs6989586621679949078 :: k3) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Lambda_6989586621680451603Sym2 t6989586621680451610 a_69895866216804515986989586621680451602 :: TyFun k3 Bool -> Type) (t6989586621680451611 :: k3) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Let6989586621679949050Scrutinee_6989586621679940366Sym3 y6989586621679949048 x6989586621679949047 key6989586621679949046 :: TyFun k3 Bool -> Type) (xys6989586621679949049 :: k3) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949050Scrutinee_6989586621679940366Sym3 y6989586621679949048 x6989586621679949047 key6989586621679949046 :: TyFun k3 Bool -> Type) (xys6989586621679949049 :: k3) = Let6989586621679949050Scrutinee_6989586621679940366 y6989586621679949048 x6989586621679949047 key6989586621679949046 xys6989586621679949049 | |
type Apply (Let6989586621679950280Scrutinee_6989586621679940348Sym3 xs6989586621679950279 x6989586621679950278 p6989586621679950274 :: TyFun k Bool -> Type) (a_69895866216799502726989586621679950275 :: k) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679950280Scrutinee_6989586621679940348Sym3 xs6989586621679950279 x6989586621679950278 p6989586621679950274 :: TyFun k Bool -> Type) (a_69895866216799502726989586621679950275 :: k) = Let6989586621679950280Scrutinee_6989586621679940348 xs6989586621679950279 x6989586621679950278 p6989586621679950274 a_69895866216799502726989586621679950275 | |
type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym4 arg_69895866216797399056989586621679740129 x6989586621679740142 y6989586621679740134 x06989586621679740133 :: TyFun k4 Bool -> Type) (arg_69895866216797399076989586621679740130 :: k4) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym4 arg_69895866216797399056989586621679740129 x6989586621679740142 y6989586621679740134 x06989586621679740133 :: TyFun k4 Bool -> Type) (arg_69895866216797399076989586621679740130 :: k4) = Let6989586621679740143Scrutinee_6989586621679739909 arg_69895866216797399056989586621679740129 x6989586621679740142 y6989586621679740134 x06989586621679740133 arg_69895866216797399076989586621679740130 | |
type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym5 arg_69895866216797399296989586621679740000 arg_69895866216797399276989586621679739999 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k5 Bool -> Type) (arg_69895866216797399316989586621679740001 :: k5) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym5 arg_69895866216797399296989586621679740000 arg_69895866216797399276989586621679739999 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k5 Bool -> Type) (arg_69895866216797399316989586621679740001 :: k5) = Let6989586621679740009Scrutinee_6989586621679739933 arg_69895866216797399296989586621679740000 arg_69895866216797399276989586621679739999 y6989586621679740006 x26989586621679740005 x16989586621679740004 arg_69895866216797399316989586621679740001 | |
type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym5 arg_69895866216797399196989586621679740057 arg_69895866216797399176989586621679740056 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k5 Bool -> Type) (arg_69895866216797399216989586621679740058 :: k5) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym5 arg_69895866216797399196989586621679740057 arg_69895866216797399176989586621679740056 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k5 Bool -> Type) (arg_69895866216797399216989586621679740058 :: k5) = Let6989586621679740066Scrutinee_6989586621679739923 arg_69895866216797399196989586621679740057 arg_69895866216797399176989586621679740056 y6989586621679740063 x26989586621679740062 x16989586621679740061 arg_69895866216797399216989586621679740058 | |
type Apply OrSym0 (a6989586621679949962 :: [Bool]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply AndSym0 (a6989586621679949966 :: [Bool]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (ListnullSym0 :: TyFun [a] Bool -> Type) (a6989586621680388179 :: [a]) | |
type Apply (NullSym0 :: TyFun [a] Bool -> Type) (a6989586621679950266 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679495349 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Maybe | |
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679495351 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Maybe | |
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680451213 :: t Bool) | |
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680451204 :: t Bool) | |
type Apply (Null_6989586621680676224Sym0 :: TyFun (Identity a) Bool -> Type) (a6989586621680676223 :: Identity a) | |
type Apply (Let6989586621680451216Scrutinee_6989586621680450974Sym0 :: TyFun (t6989586621680450727 Bool) All -> Type) (x6989586621680451215 :: t6989586621680450727 Bool) | |
type Apply (Let6989586621680451207Scrutinee_6989586621680450976Sym0 :: TyFun (t6989586621680450727 Bool) Any -> Type) (x6989586621680451206 :: t6989586621680450727 Bool) | |
type Apply (ListelemSym1 a6989586621680388261 :: TyFun [a] Bool -> Type) (a6989586621680388262 :: [a]) | |
type Apply (ListisPrefixOfSym1 a6989586621680388326 :: TyFun [a] Bool -> Type) (a6989586621680388327 :: [a]) | |
type Apply (NotElemSym1 a6989586621679949635 :: TyFun [a] Bool -> Type) (a6989586621679949636 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (ElemSym1 a6989586621679949642 :: TyFun [a] Bool -> Type) (a6989586621679949643 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (IsPrefixOfSym1 a6989586621679949669 :: TyFun [a] Bool -> Type) (a6989586621679949670 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym1 a6989586621679949669 :: TyFun [a] Bool -> Type) (a6989586621679949670 :: [a]) = IsPrefixOf a6989586621679949669 a6989586621679949670 | |
type Apply (AnySym1 a6989586621679949900 :: TyFun [a] Bool -> Type) (a6989586621679949901 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (IsInfixOfSym1 a6989586621679949907 :: TyFun [a] Bool -> Type) (a6989586621679949908 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (AllSym1 a6989586621679949955 :: TyFun [a] Bool -> Type) (a6989586621679949956 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (IsSuffixOfSym1 a6989586621679950260 :: TyFun [a] Bool -> Type) (a6989586621679950261 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym1 a6989586621679950260 :: TyFun [a] Bool -> Type) (a6989586621679950261 :: [a]) = IsSuffixOf a6989586621679950260 a6989586621679950261 | |
type Apply (Elem_6989586621680676101Sym1 a6989586621680676099 :: TyFun (Identity a) Bool -> Type) (a6989586621680676100 :: Identity a) | |
type Apply (Elem_bySym2 a6989586621679948928 a6989586621679948927 :: TyFun [a] Bool -> Type) (a6989586621679948929 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Elem_6989586621680451653Sym1 a6989586621680451651 t :: TyFun (t a) Bool -> Type) (a6989586621680451652 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Null_6989586621680451616Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451615 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (AnySym1 a6989586621680451191 t :: TyFun (t a) Bool -> Type) (a6989586621680451192 :: t a) | |
type Apply (ElemSym1 arg6989586621680451394 t :: TyFun (t a) Bool -> Type) (arg6989586621680451395 :: t a) | |
type Apply (NotElemSym1 a6989586621680451120 t :: TyFun (t a) Bool -> Type) (a6989586621680451121 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (arg6989586621680451390 :: t a) | |
type Apply (AllSym1 a6989586621680451178 t :: TyFun (t a) Bool -> Type) (a6989586621680451179 :: t a) | |
type Apply (Elem_6989586621680451776Sym1 a6989586621680451774 t :: TyFun (t a) Bool -> Type) (a6989586621680451775 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Null_6989586621680451914Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680451913 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Null_6989586621680452090Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680452089 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Elem_6989586621680452113Sym1 a6989586621680452111 t :: TyFun (t a) Bool -> Type) (a6989586621680452112 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Null_6989586621680452236Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680452235 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Elem_6989586621680452280Sym1 a6989586621680452278 t :: TyFun (t a) Bool -> Type) (a6989586621680452279 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Null_6989586621680452403Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680452402 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Elem_6989586621680452447Sym1 a6989586621680452445 t :: TyFun (t a) Bool -> Type) (a6989586621680452446 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Null_6989586621680452570Sym0 :: TyFun (t a) Bool -> Type) (a6989586621680452569 :: t a) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Let6989586621679949661Scrutinee_6989586621679940374Sym3 xs6989586621679949659 x6989586621679949658 l6989586621679949651 :: TyFun [k1] Bool -> Type) (ls6989586621679949660 :: [k1]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949661Scrutinee_6989586621679940374Sym3 xs6989586621679949659 x6989586621679949658 l6989586621679949651 :: TyFun [k1] Bool -> Type) (ls6989586621679949660 :: [k1]) = Let6989586621679949661Scrutinee_6989586621679940374 xs6989586621679949659 x6989586621679949658 l6989586621679949651 ls6989586621679949660 | |
type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym4 ys6989586621679948951 y6989586621679948950 l6989586621679948942 eq6989586621679948941 :: TyFun [k2] Bool -> Type) (xs6989586621679948952 :: [k2]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym4 ys6989586621679948951 y6989586621679948950 l6989586621679948942 eq6989586621679948941 :: TyFun [k2] Bool -> Type) (xs6989586621679948952 :: [k2]) = Let6989586621679948953Scrutinee_6989586621679940376 ys6989586621679948951 y6989586621679948950 l6989586621679948942 eq6989586621679948941 xs6989586621679948952 | |
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680432540 :: Either a b) | |
Defined in Data.Singletons.Prelude.Either | |
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680432542 :: Either a b) | |
Defined in Data.Singletons.Prelude.Either | |
type Apply (TFHelper_6989586621680882853Sym1 a6989586621680882851 :: TyFun (Arg a b) Bool -> Type) (a6989586621680882852 :: Arg a b) | |
type Apply (GuardSym0 :: TyFun Bool (f6989586621679544591 ()) -> Type) (a6989586621679544760 :: Bool) | |
type Apply (||@#@$) (a6989586621679360668 :: Bool) | |
Defined in Data.Singletons.Prelude.Bool | |
type Apply (&&@#@$) (a6989586621679360427 :: Bool) | |
Defined in Data.Singletons.Prelude.Bool | |
type Apply Compare_6989586621679391374Sym0 (a6989586621679391372 :: Bool) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply ShowsPrec_6989586621680280967Sym0 (a6989586621680280964 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (<=?@#@$) (a3530822107858468865 :: Nat) | |
Defined in Data.Singletons.TypeLits.Internal | |
type Apply ShowParenSym0 (a6989586621680262625 :: Bool) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (Let6989586621680442523Scrutinee_6989586621680442486Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680442516 :: k1) | |
type Apply (Let6989586621680442550Scrutinee_6989586621680442488Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621680442543 :: k1) | |
type Apply (Let6989586621679380100Scrutinee_6989586621679379995Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679380098 :: k1) | |
type Apply (Let6989586621679380214Scrutinee_6989586621679380009Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679380212 :: k1) | |
type Apply (Let6989586621679380196Scrutinee_6989586621679380007Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679380194 :: k1) | |
type Apply (Let6989586621679380105Scrutinee_6989586621679379997Sym0 :: TyFun k1 (TyFun k1 Bool -> Type) -> Type) (x6989586621679380098 :: k1) | |
type Apply (ListelemSym0 :: TyFun a6989586621680387262 ([a6989586621680387262] ~> Bool) -> Type) (a6989586621680388261 :: a6989586621680387262) | |
type Apply (NotElemSym0 :: TyFun a6989586621679939751 ([a6989586621679939751] ~> Bool) -> Type) (a6989586621679949635 :: a6989586621679939751) | |
type Apply (ElemSym0 :: TyFun a6989586621679939752 ([a6989586621679939752] ~> Bool) -> Type) (a6989586621679949642 :: a6989586621679939752) | |
type Apply (ShowsPrec_6989586621680280967Sym1 a6989586621680280964 :: TyFun Bool (Symbol ~> Symbol) -> Type) (a6989586621680280965 :: Bool) | |
type Apply (WhenSym0 :: TyFun Bool (f6989586621679544620 () ~> f6989586621679544620 ()) -> Type) (a6989586621679545008 :: Bool) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (Bool_Sym0 :: TyFun a6989586621679359676 (a6989586621679359676 ~> (Bool ~> a6989586621679359676)) -> Type) (a6989586621679359682 :: a6989586621679359676) | |
type Apply ((==@#@$) :: TyFun a6989586621679363696 (a6989586621679363696 ~> Bool) -> Type) (x6989586621679363697 :: a6989586621679363696) | |
type Apply ((/=@#@$) :: TyFun a6989586621679363696 (a6989586621679363696 ~> Bool) -> Type) (x6989586621679363699 :: a6989586621679363696) | |
type Apply (DefaultEqSym0 :: TyFun k6989586621679363690 (k6989586621679363690 ~> Bool) -> Type) (a6989586621679363691 :: k6989586621679363690) | |
Defined in Data.Singletons.Prelude.Eq type Apply (DefaultEqSym0 :: TyFun k6989586621679363690 (k6989586621679363690 ~> Bool) -> Type) (a6989586621679363691 :: k6989586621679363690) = DefaultEqSym1 a6989586621679363691 | |
type Apply (TFHelper_6989586621679380186Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) (a6989586621679380184 :: a6989586621679379977) | |
type Apply (TFHelper_6989586621679380168Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) (a6989586621679380166 :: a6989586621679379977) | |
type Apply (TFHelper_6989586621679380150Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) (a6989586621679380148 :: a6989586621679379977) | |
type Apply (TFHelper_6989586621679380132Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) (a6989586621679380130 :: a6989586621679379977) | |
type Apply ((<=@#@$) :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) (arg6989586621679380074 :: a6989586621679379977) | |
type Apply ((>=@#@$) :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) (arg6989586621679380082 :: a6989586621679379977) | |
type Apply ((>@#@$) :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) (arg6989586621679380078 :: a6989586621679379977) | |
type Apply ((<@#@$) :: TyFun a6989586621679379977 (a6989586621679379977 ~> Bool) -> Type) (arg6989586621679380070 :: a6989586621679379977) | |
type Apply (UnlessSym0 :: TyFun Bool (f6989586621681207764 () ~> f6989586621681207764 ()) -> Type) (a6989586621681208132 :: Bool) | |
Defined in Data.Singletons.Prelude.Monad type Apply (UnlessSym0 :: TyFun Bool (f6989586621681207764 () ~> f6989586621681207764 ()) -> Type) (a6989586621681208132 :: Bool) = (UnlessSym1 a6989586621681208132 f6989586621681207764 :: TyFun (f6989586621681207764 ()) (f6989586621681207764 ()) -> Type) | |
type Apply (Elem_6989586621680676101Sym0 :: TyFun a6989586621680450744 (Identity a6989586621680450744 ~> Bool) -> Type) (a6989586621680676099 :: a6989586621680450744) | |
type Apply (Let6989586621679948982Scrutinee_6989586621679940370Sym0 :: TyFun k1 (TyFun k Bool -> Type) -> Type) (n6989586621679948980 :: k1) | |
type Apply (Bool_Sym1 a6989586621679359682 :: TyFun a6989586621679359676 (Bool ~> a6989586621679359676) -> Type) (a6989586621679359683 :: a6989586621679359676) | |
type Apply (Elem_bySym1 a6989586621679948927 :: TyFun a6989586621679939669 ([a6989586621679939669] ~> Bool) -> Type) (a6989586621679948928 :: a6989586621679939669) | |
type Apply (Elem_6989586621680451653Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680451651 :: a6989586621680450744) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Elem_6989586621680451653Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680451651 :: a6989586621680450744) = (Elem_6989586621680451653Sym1 a6989586621680451651 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
type Apply (ElemSym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (arg6989586621680451394 :: a6989586621680450744) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (NotElemSym0 :: TyFun a6989586621680450638 (t6989586621680450637 a6989586621680450638 ~> Bool) -> Type) (a6989586621680451120 :: a6989586621680450638) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (NotElemSym0 :: TyFun a6989586621680450638 (t6989586621680450637 a6989586621680450638 ~> Bool) -> Type) (a6989586621680451120 :: a6989586621680450638) = (NotElemSym1 a6989586621680451120 t6989586621680450637 :: TyFun (t6989586621680450637 a6989586621680450638) Bool -> Type) | |
type Apply (Elem_6989586621680451776Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680451774 :: a6989586621680450744) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Elem_6989586621680451776Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680451774 :: a6989586621680450744) = (Elem_6989586621680451776Sym1 a6989586621680451774 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
type Apply (Elem_6989586621680452113Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680452111 :: a6989586621680450744) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Elem_6989586621680452113Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680452111 :: a6989586621680450744) = (Elem_6989586621680452113Sym1 a6989586621680452111 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
type Apply (Elem_6989586621680452280Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680452278 :: a6989586621680450744) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Elem_6989586621680452280Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680452278 :: a6989586621680450744) = (Elem_6989586621680452280Sym1 a6989586621680452278 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
type Apply (Elem_6989586621680452447Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680452445 :: a6989586621680450744) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Elem_6989586621680452447Sym0 :: TyFun a6989586621680450744 (t6989586621680450727 a6989586621680450744 ~> Bool) -> Type) (a6989586621680452445 :: a6989586621680450744) = (Elem_6989586621680452447Sym1 a6989586621680452445 t6989586621680450727 :: TyFun (t6989586621680450727 a6989586621680450744) Bool -> Type) | |
type Apply (Let6989586621679948969Scrutinee_6989586621679940372Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679948966 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949050Scrutinee_6989586621679940366Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621679949046 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949050Scrutinee_6989586621679940366Sym0 :: TyFun k1 (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) (key6989586621679949046 :: k1) = (Let6989586621679949050Scrutinee_6989586621679940366Sym1 key6989586621679949046 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679949065Scrutinee_6989586621679940356Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679949062 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949079Scrutinee_6989586621679940354Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (n6989586621679949076 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949661Scrutinee_6989586621679940374Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679949651 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949661Scrutinee_6989586621679940374Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679949651 :: k1) = (Let6989586621679949661Scrutinee_6989586621679940374Sym1 l6989586621679949651 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) | |
type Apply (Lambda_6989586621680451603Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (a_69895866216804515986989586621680451602 :: k1) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Lambda_6989586621681208272Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool (TyFun [k2] [k2] -> Type) -> Type) -> Type) -> Type) -> Type) (p6989586621681208267 :: k1) | |
Defined in Data.Singletons.Prelude.Monad type Apply (Lambda_6989586621681208272Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun Bool (TyFun [k2] [k2] -> Type) -> Type) -> Type) -> Type) -> Type) (p6989586621681208267 :: k1) = (Lambda_6989586621681208272Sym1 p6989586621681208267 :: TyFun k2 (TyFun k3 (TyFun Bool (TyFun [k2] [k2] -> Type) -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679950280Scrutinee_6989586621679940348Sym1 p6989586621679950274 :: TyFun k1 (TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) -> Type) (x6989586621679950278 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679950280Scrutinee_6989586621679940348Sym1 p6989586621679950274 :: TyFun k1 (TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) -> Type) (x6989586621679950278 :: k1) = (Let6989586621679950280Scrutinee_6989586621679940348Sym2 p6989586621679950274 x6989586621679950278 :: TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) | |
type Apply (Let6989586621679948969Scrutinee_6989586621679940372Sym1 x6989586621679948966 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (xs6989586621679948967 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949050Scrutinee_6989586621679940366Sym1 key6989586621679949046 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679949047 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949050Scrutinee_6989586621679940366Sym1 key6989586621679949046 :: TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) (x6989586621679949047 :: k1) = (Let6989586621679949050Scrutinee_6989586621679940366Sym2 key6989586621679949046 x6989586621679949047 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) | |
type Apply (Let6989586621679949065Scrutinee_6989586621679940356Sym1 n6989586621679949062 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679949063 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949079Scrutinee_6989586621679940354Sym1 n6989586621679949076 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (x6989586621679949077 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym1 eq6989586621679948941 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679948942 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym1 eq6989586621679948941 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) -> Type) (l6989586621679948942 :: k1) = (Let6989586621679948953Scrutinee_6989586621679940376Sym2 eq6989586621679948941 l6989586621679948942 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679949661Scrutinee_6989586621679940374Sym1 l6989586621679949651 :: TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) (x6989586621679949658 :: k1) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949661Scrutinee_6989586621679940374Sym1 l6989586621679949651 :: TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) (x6989586621679949658 :: k1) = (Let6989586621679949661Scrutinee_6989586621679940374Sym2 l6989586621679949651 x6989586621679949658 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type) | |
type Apply (Lambda_6989586621680451603Sym1 a_69895866216804515986989586621680451602 :: TyFun k1 (TyFun k3 Bool -> Type) -> Type) (t6989586621680451610 :: k1) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x06989586621679740133 :: k1) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym0 :: TyFun k1 (TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x06989586621679740133 :: k1) = (Let6989586621679740143Scrutinee_6989586621679739909Sym1 x06989586621679740133 :: TyFun k2 (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) | |
type Apply (Lambda_6989586621681208272Sym1 p6989586621681208267 :: TyFun k1 (TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) -> Type) (x6989586621681208271 :: k1) | |
Defined in Data.Singletons.Prelude.Monad type Apply (Lambda_6989586621681208272Sym1 p6989586621681208267 :: TyFun k1 (TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) -> Type) (x6989586621681208271 :: k1) = (Lambda_6989586621681208272Sym2 p6989586621681208267 x6989586621681208271 :: TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) | |
type Apply (Lambda_6989586621681208272Sym2 x6989586621681208271 p6989586621681208267 :: TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) (a_69895866216812082656989586621681208268 :: k3) | |
Defined in Data.Singletons.Prelude.Monad type Apply (Lambda_6989586621681208272Sym2 x6989586621681208271 p6989586621681208267 :: TyFun k3 (TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) -> Type) (a_69895866216812082656989586621681208268 :: k3) = Lambda_6989586621681208272Sym3 x6989586621681208271 p6989586621681208267 a_69895866216812082656989586621681208268 | |
type Apply (Let6989586621679949661Scrutinee_6989586621679940374Sym2 x6989586621679949658 l6989586621679949651 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type) (xs6989586621679949659 :: k3) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949661Scrutinee_6989586621679940374Sym2 x6989586621679949658 l6989586621679949651 :: TyFun k3 (TyFun [k1] Bool -> Type) -> Type) (xs6989586621679949659 :: k3) = Let6989586621679949661Scrutinee_6989586621679940374Sym3 x6989586621679949658 l6989586621679949651 xs6989586621679949659 | |
type Apply (Let6989586621679949050Scrutinee_6989586621679940366Sym2 x6989586621679949047 key6989586621679949046 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621679949048 :: k2) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949050Scrutinee_6989586621679940366Sym2 x6989586621679949047 key6989586621679949046 :: TyFun k2 (TyFun k3 Bool -> Type) -> Type) (y6989586621679949048 :: k2) = (Let6989586621679949050Scrutinee_6989586621679940366Sym3 x6989586621679949047 key6989586621679949046 y6989586621679949048 :: TyFun k3 Bool -> Type) | |
type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym2 l6989586621679948942 eq6989586621679948941 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) (y6989586621679948950 :: k2) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym2 l6989586621679948942 eq6989586621679948941 :: TyFun k2 (TyFun k3 (TyFun [k2] Bool -> Type) -> Type) -> Type) (y6989586621679948950 :: k2) = (Let6989586621679948953Scrutinee_6989586621679940376Sym3 l6989586621679948942 eq6989586621679948941 y6989586621679948950 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type) | |
type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679740004 :: k1) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679740004 :: k1) = (Let6989586621679740009Scrutinee_6989586621679739933Sym1 x16989586621679740004 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679740061 :: k1) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym0 :: TyFun k1 (TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x16989586621679740061 :: k1) = (Let6989586621679740066Scrutinee_6989586621679739923Sym1 x16989586621679740061 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym1 x06989586621679740133 :: TyFun k1 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679740134 :: k1) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym1 x06989586621679740133 :: TyFun k1 (TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679740134 :: k1) = (Let6989586621679740143Scrutinee_6989586621679739909Sym2 x06989586621679740133 y6989586621679740134 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym3 y6989586621679948950 l6989586621679948942 eq6989586621679948941 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type) (ys6989586621679948951 :: k3) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym3 y6989586621679948950 l6989586621679948942 eq6989586621679948941 :: TyFun k3 (TyFun [k2] Bool -> Type) -> Type) (ys6989586621679948951 :: k3) = Let6989586621679948953Scrutinee_6989586621679940376Sym4 y6989586621679948950 l6989586621679948942 eq6989586621679948941 ys6989586621679948951 | |
type Apply (Lambda_6989586621681208272Sym3 a_69895866216812082656989586621681208268 x6989586621681208271 p6989586621681208267 :: TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) (t6989586621681208278 :: Bool) | |
Defined in Data.Singletons.Prelude.Monad type Apply (Lambda_6989586621681208272Sym3 a_69895866216812082656989586621681208268 x6989586621681208271 p6989586621681208267 :: TyFun Bool (TyFun [k1] [k1] -> Type) -> Type) (t6989586621681208278 :: Bool) = Lambda_6989586621681208272 a_69895866216812082656989586621681208268 x6989586621681208271 p6989586621681208267 t6989586621681208278 | |
type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym1 x16989586621679740004 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679740005 :: k1) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym1 x16989586621679740004 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679740005 :: k1) = (Let6989586621679740009Scrutinee_6989586621679739933Sym2 x16989586621679740004 x26989586621679740005 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym1 x16989586621679740061 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679740062 :: k1) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym1 x16989586621679740061 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (x26989586621679740062 :: k1) = (Let6989586621679740066Scrutinee_6989586621679739923Sym2 x16989586621679740061 x26989586621679740062 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym2 y6989586621679740134 x06989586621679740133 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (x6989586621679740142 :: k1) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym2 y6989586621679740134 x06989586621679740133 :: TyFun k1 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) (x6989586621679740142 :: k1) = (Let6989586621679740143Scrutinee_6989586621679739909Sym3 y6989586621679740134 x06989586621679740133 x6989586621679740142 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) | |
type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym2 x26989586621679740005 x16989586621679740004 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679740006 :: k2) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym2 x26989586621679740005 x16989586621679740004 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679740006 :: k2) = (Let6989586621679740009Scrutinee_6989586621679739933Sym3 x26989586621679740005 x16989586621679740004 y6989586621679740006 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym2 x26989586621679740062 x16989586621679740061 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679740063 :: k2) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym2 x26989586621679740062 x16989586621679740061 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) -> Type) (y6989586621679740063 :: k2) = (Let6989586621679740066Scrutinee_6989586621679739923Sym3 x26989586621679740062 x16989586621679740061 y6989586621679740063 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym3 x6989586621679740142 y6989586621679740134 x06989586621679740133 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216797399056989586621679740129 :: k3) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740143Scrutinee_6989586621679739909Sym3 x6989586621679740142 y6989586621679740134 x06989586621679740133 :: TyFun k3 (TyFun k4 Bool -> Type) -> Type) (arg_69895866216797399056989586621679740129 :: k3) = (Let6989586621679740143Scrutinee_6989586621679739909Sym4 x6989586621679740142 y6989586621679740134 x06989586621679740133 arg_69895866216797399056989586621679740129 :: TyFun k4 Bool -> Type) | |
type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym3 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797399276989586621679739999 :: k3) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym3 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797399276989586621679739999 :: k3) = (Let6989586621679740009Scrutinee_6989586621679739933Sym4 y6989586621679740006 x26989586621679740005 x16989586621679740004 arg_69895866216797399276989586621679739999 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) | |
type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym3 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797399176989586621679740056 :: k3) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym3 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k3 (TyFun k4 (TyFun k5 Bool -> Type) -> Type) -> Type) (arg_69895866216797399176989586621679740056 :: k3) = (Let6989586621679740066Scrutinee_6989586621679739923Sym4 y6989586621679740063 x26989586621679740062 x16989586621679740061 arg_69895866216797399176989586621679740056 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) | |
type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym4 arg_69895866216797399276989586621679739999 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797399296989586621679740000 :: k4) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740009Scrutinee_6989586621679739933Sym4 arg_69895866216797399276989586621679739999 y6989586621679740006 x26989586621679740005 x16989586621679740004 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797399296989586621679740000 :: k4) = (Let6989586621679740009Scrutinee_6989586621679739933Sym5 arg_69895866216797399276989586621679739999 y6989586621679740006 x26989586621679740005 x16989586621679740004 arg_69895866216797399296989586621679740000 :: TyFun k5 Bool -> Type) | |
type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym4 arg_69895866216797399176989586621679740056 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797399196989586621679740057 :: k4) | |
Defined in Data.Singletons.Prelude.Enum type Apply (Let6989586621679740066Scrutinee_6989586621679739923Sym4 arg_69895866216797399176989586621679740056 y6989586621679740063 x26989586621679740062 x16989586621679740061 :: TyFun k4 (TyFun k5 Bool -> Type) -> Type) (arg_69895866216797399196989586621679740057 :: k4) = (Let6989586621679740066Scrutinee_6989586621679739923Sym5 arg_69895866216797399176989586621679740056 y6989586621679740063 x26989586621679740062 x16989586621679740061 arg_69895866216797399196989586621679740057 :: TyFun k5 Bool -> Type) | |
type Apply (ListisPrefixOfSym0 :: TyFun [a6989586621680387274] ([a6989586621680387274] ~> Bool) -> Type) (a6989586621680388326 :: [a6989586621680387274]) | |
type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679939755] ([a6989586621679939755] ~> Bool) -> Type) (a6989586621679949669 :: [a6989586621679939755]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsPrefixOfSym0 :: TyFun [a6989586621679939755] ([a6989586621679939755] ~> Bool) -> Type) (a6989586621679949669 :: [a6989586621679939755]) = IsPrefixOfSym1 a6989586621679949669 | |
type Apply (IsInfixOfSym0 :: TyFun [a6989586621679939753] ([a6989586621679939753] ~> Bool) -> Type) (a6989586621679949907 :: [a6989586621679939753]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsInfixOfSym0 :: TyFun [a6989586621679939753] ([a6989586621679939753] ~> Bool) -> Type) (a6989586621679949907 :: [a6989586621679939753]) = IsInfixOfSym1 a6989586621679949907 | |
type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679939754] ([a6989586621679939754] ~> Bool) -> Type) (a6989586621679950260 :: [a6989586621679939754]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IsSuffixOfSym0 :: TyFun [a6989586621679939754] ([a6989586621679939754] ~> Bool) -> Type) (a6989586621679950260 :: [a6989586621679939754]) = IsSuffixOfSym1 a6989586621679950260 | |
type Apply (Let6989586621679950280Scrutinee_6989586621679940348Sym2 x6989586621679950278 p6989586621679950274 :: TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) (xs6989586621679950279 :: [a6989586621679939789]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679950280Scrutinee_6989586621679940348Sym2 x6989586621679950278 p6989586621679950274 :: TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) (xs6989586621679950279 :: [a6989586621679939789]) = (Let6989586621679950280Scrutinee_6989586621679940348Sym3 x6989586621679950278 p6989586621679950274 xs6989586621679950279 :: TyFun k Bool -> Type) | |
type Apply (Let6989586621679949110ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679949097 :: k ~> Bool) | |
type Apply (Let6989586621679949110YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679949097 :: k ~> Bool) | |
type Apply (Let6989586621679949110X_6989586621679949111Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679949097 :: k ~> Bool) | |
type Apply (Let6989586621679949153ZsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679949140 :: k ~> Bool) | |
type Apply (Let6989586621679949153YsSym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] [k] -> Type) -> Type) -> Type) (p6989586621679949140 :: k ~> Bool) | |
type Apply (Let6989586621679949153X_6989586621679949154Sym0 :: TyFun (k ~> Bool) (TyFun k (TyFun [k] ([k], [k]) -> Type) -> Type) -> Type) (p6989586621679949140 :: k ~> Bool) | |
type Apply (ListnubBySym0 :: TyFun (a6989586621680387268 ~> (a6989586621680387268 ~> Bool)) ([a6989586621680387268] ~> [a6989586621680387268]) -> Type) (a6989586621680388291 :: a6989586621680387268 ~> (a6989586621680387268 ~> Bool)) | |
type Apply (ListpartitionSym0 :: TyFun (a6989586621680387276 ~> Bool) ([a6989586621680387276] ~> ([a6989586621680387276], [a6989586621680387276])) -> Type) (a6989586621680388346 :: a6989586621680387276 ~> Bool) | |
type Apply (ListfilterSym0 :: TyFun (a6989586621680387277 ~> Bool) ([a6989586621680387277] ~> [a6989586621680387277]) -> Type) (a6989586621680388356 :: a6989586621680387277 ~> Bool) | |
type Apply (ListspanSym0 :: TyFun (a6989586621680387278 ~> Bool) ([a6989586621680387278] ~> ([a6989586621680387278], [a6989586621680387278])) -> Type) (a6989586621680388366 :: a6989586621680387278 ~> Bool) | |
type Apply (ListdropWhileSym0 :: TyFun (a6989586621680387279 ~> Bool) ([a6989586621680387279] ~> [a6989586621680387279]) -> Type) (a6989586621680388376 :: a6989586621680387279 ~> Bool) | |
type Apply (ListtakeWhileSym0 :: TyFun (a6989586621680387280 ~> Bool) ([a6989586621680387280] ~> [a6989586621680387280]) -> Type) (a6989586621680388386 :: a6989586621680387280 ~> Bool) | |
type Apply (NubBySym0 :: TyFun (a6989586621679939670 ~> (a6989586621679939670 ~> Bool)) ([a6989586621679939670] ~> [a6989586621679939670]) -> Type) (a6989586621679948937 :: a6989586621679939670 ~> (a6989586621679939670 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (PartitionSym0 :: TyFun (a6989586621679939679 ~> Bool) ([a6989586621679939679] ~> ([a6989586621679939679], [a6989586621679939679])) -> Type) (a6989586621679949035 :: a6989586621679939679 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (PartitionSym0 :: TyFun (a6989586621679939679 ~> Bool) ([a6989586621679939679] ~> ([a6989586621679939679], [a6989586621679939679])) -> Type) (a6989586621679949035 :: a6989586621679939679 ~> Bool) = PartitionSym1 a6989586621679949035 | |
type Apply (BreakSym0 :: TyFun (a6989586621679939691 ~> Bool) ([a6989586621679939691] ~> ([a6989586621679939691], [a6989586621679939691])) -> Type) (a6989586621679949092 :: a6989586621679939691 ~> Bool) | |
type Apply (SpanSym0 :: TyFun (a6989586621679939692 ~> Bool) ([a6989586621679939692] ~> ([a6989586621679939692], [a6989586621679939692])) -> Type) (a6989586621679949135 :: a6989586621679939692 ~> Bool) | |
type Apply (GroupBySym0 :: TyFun (a6989586621679939682 ~> (a6989586621679939682 ~> Bool)) ([a6989586621679939682] ~> [[a6989586621679939682]]) -> Type) (a6989586621679949178 :: a6989586621679939682 ~> (a6989586621679939682 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (DropWhileSym0 :: TyFun (a6989586621679939694 ~> Bool) ([a6989586621679939694] ~> [a6989586621679939694]) -> Type) (a6989586621679949212 :: a6989586621679939694 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileSym0 :: TyFun (a6989586621679939694 ~> Bool) ([a6989586621679939694] ~> [a6989586621679939694]) -> Type) (a6989586621679949212 :: a6989586621679939694 ~> Bool) = DropWhileSym1 a6989586621679949212 | |
type Apply (TakeWhileSym0 :: TyFun (a6989586621679939695 ~> Bool) ([a6989586621679939695] ~> [a6989586621679939695]) -> Type) (a6989586621679949230 :: a6989586621679939695 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (TakeWhileSym0 :: TyFun (a6989586621679939695 ~> Bool) ([a6989586621679939695] ~> [a6989586621679939695]) -> Type) (a6989586621679949230 :: a6989586621679939695 ~> Bool) = TakeWhileSym1 a6989586621679949230 | |
type Apply (FilterSym0 :: TyFun (a6989586621679939703 ~> Bool) ([a6989586621679939703] ~> [a6989586621679939703]) -> Type) (a6989586621679949244 :: a6989586621679939703 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (FilterSym0 :: TyFun (a6989586621679939703 ~> Bool) ([a6989586621679939703] ~> [a6989586621679939703]) -> Type) (a6989586621679949244 :: a6989586621679939703 ~> Bool) = FilterSym1 a6989586621679949244 | |
type Apply (FindSym0 :: TyFun (a6989586621679939702 ~> Bool) ([a6989586621679939702] ~> Maybe a6989586621679939702) -> Type) (a6989586621679949259 :: a6989586621679939702 ~> Bool) | |
type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679939708 ~> (a6989586621679939708 ~> Bool)) ([a6989586621679939708] ~> ([a6989586621679939708] ~> [a6989586621679939708])) -> Type) (a6989586621679949328 :: a6989586621679939708 ~> (a6989586621679939708 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DeleteFirstsBySym0 :: TyFun (a6989586621679939708 ~> (a6989586621679939708 ~> Bool)) ([a6989586621679939708] ~> ([a6989586621679939708] ~> [a6989586621679939708])) -> Type) (a6989586621679949328 :: a6989586621679939708 ~> (a6989586621679939708 ~> Bool)) = DeleteFirstsBySym1 a6989586621679949328 | |
type Apply (UnionBySym0 :: TyFun (a6989586621679939668 ~> (a6989586621679939668 ~> Bool)) ([a6989586621679939668] ~> ([a6989586621679939668] ~> [a6989586621679939668])) -> Type) (a6989586621679949341 :: a6989586621679939668 ~> (a6989586621679939668 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (FindIndicesSym0 :: TyFun (a6989586621679939698 ~> Bool) ([a6989586621679939698] ~> [Nat]) -> Type) (a6989586621679949585 :: a6989586621679939698 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (FindIndexSym0 :: TyFun (a6989586621679939699 ~> Bool) ([a6989586621679939699] ~> Maybe Nat) -> Type) (a6989586621679949619 :: a6989586621679939699 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (AnySym0 :: TyFun (a6989586621679939772 ~> Bool) ([a6989586621679939772] ~> Bool) -> Type) (a6989586621679949900 :: a6989586621679939772 ~> Bool) | |
type Apply (IntersectBySym0 :: TyFun (a6989586621679939696 ~> (a6989586621679939696 ~> Bool)) ([a6989586621679939696] ~> ([a6989586621679939696] ~> [a6989586621679939696])) -> Type) (a6989586621679949913 :: a6989586621679939696 ~> (a6989586621679939696 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (IntersectBySym0 :: TyFun (a6989586621679939696 ~> (a6989586621679939696 ~> Bool)) ([a6989586621679939696] ~> ([a6989586621679939696] ~> [a6989586621679939696])) -> Type) (a6989586621679949913 :: a6989586621679939696 ~> (a6989586621679939696 ~> Bool)) = IntersectBySym1 a6989586621679949913 | |
type Apply (AllSym0 :: TyFun (a6989586621679939773 ~> Bool) ([a6989586621679939773] ~> Bool) -> Type) (a6989586621679949955 :: a6989586621679939773 ~> Bool) | |
type Apply (DropWhileEndSym0 :: TyFun (a6989586621679939693 ~> Bool) ([a6989586621679939693] ~> [a6989586621679939693]) -> Type) (a6989586621679950268 :: a6989586621679939693 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (DropWhileEndSym0 :: TyFun (a6989586621679939693 ~> Bool) ([a6989586621679939693] ~> [a6989586621679939693]) -> Type) (a6989586621679950268 :: a6989586621679939693 ~> Bool) = DropWhileEndSym1 a6989586621679950268 | |
type Apply (Elem_bySym0 :: TyFun (a6989586621679939669 ~> (a6989586621679939669 ~> Bool)) (a6989586621679939669 ~> ([a6989586621679939669] ~> Bool)) -> Type) (a6989586621679948927 :: a6989586621679939669 ~> (a6989586621679939669 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (SelectSym0 :: TyFun (a6989586621679939678 ~> Bool) (a6989586621679939678 ~> (([a6989586621679939678], [a6989586621679939678]) ~> ([a6989586621679939678], [a6989586621679939678]))) -> Type) (a6989586621679949017 :: a6989586621679939678 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (DeleteBySym0 :: TyFun (a6989586621679939709 ~> (a6989586621679939709 ~> Bool)) (a6989586621679939709 ~> ([a6989586621679939709] ~> [a6989586621679939709])) -> Type) (a6989586621679949310 :: a6989586621679939709 ~> (a6989586621679939709 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (UntilSym0 :: TyFun (a6989586621679520379 ~> Bool) ((a6989586621679520379 ~> a6989586621679520379) ~> (a6989586621679520379 ~> a6989586621679520379)) -> Type) (a6989586621679520504 :: a6989586621679520379 ~> Bool) | |
type Apply (Let6989586621679948943NubBy'Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k (TyFun [k1] ([k1] ~> [k1]) -> Type) -> Type) -> Type) (eq6989586621679948941 :: k1 ~> (k1 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949185ZsSym0 :: TyFun (k1 ~> (a6989586621679939692 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939692] [a6989586621679939692] -> Type) -> Type) -> Type) (eq6989586621679949182 :: k1 ~> (a6989586621679939692 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949185YsSym0 :: TyFun (k1 ~> (a6989586621679939692 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939692] [a6989586621679939692] -> Type) -> Type) -> Type) (eq6989586621679949182 :: k1 ~> (a6989586621679939692 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (Let6989586621679949185X_6989586621679949186Sym0 :: TyFun (k1 ~> (a6989586621679939692 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939692] ([a6989586621679939692], [a6989586621679939692]) -> Type) -> Type) -> Type) (eq6989586621679949182 :: k1 ~> (a6989586621679939692 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679949185X_6989586621679949186Sym0 :: TyFun (k1 ~> (a6989586621679939692 ~> Bool)) (TyFun k1 (TyFun [a6989586621679939692] ([a6989586621679939692], [a6989586621679939692]) -> Type) -> Type) -> Type) (eq6989586621679949182 :: k1 ~> (a6989586621679939692 ~> Bool)) = Let6989586621679949185X_6989586621679949186Sym1 eq6989586621679949182 | |
type Apply (Lambda_6989586621679950276Sym0 :: TyFun (a6989586621679939789 ~> Bool) (TyFun k (TyFun a6989586621679939789 (TyFun [a6989586621679939789] [a6989586621679939789] -> Type) -> Type) -> Type) -> Type) (p6989586621679950274 :: a6989586621679939789 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Lambda_6989586621679950276Sym0 :: TyFun (a6989586621679939789 ~> Bool) (TyFun k (TyFun a6989586621679939789 (TyFun [a6989586621679939789] [a6989586621679939789] -> Type) -> Type) -> Type) -> Type) (p6989586621679950274 :: a6989586621679939789 ~> Bool) = (Lambda_6989586621679950276Sym1 p6989586621679950274 :: TyFun k (TyFun a6989586621679939789 (TyFun [a6989586621679939789] [a6989586621679939789] -> Type) -> Type) -> Type) | |
type Apply (Lambda_6989586621680451100Sym0 :: TyFun (a6989586621679072651 ~> Bool) (TyFun k (TyFun a6989586621679072651 (First a6989586621679072651) -> Type) -> Type) -> Type) (p6989586621680451097 :: a6989586621679072651 ~> Bool) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Lambda_6989586621680451100Sym0 :: TyFun (a6989586621679072651 ~> Bool) (TyFun k (TyFun a6989586621679072651 (First a6989586621679072651) -> Type) -> Type) -> Type) (p6989586621680451097 :: a6989586621679072651 ~> Bool) = (Lambda_6989586621680451100Sym1 p6989586621680451097 :: TyFun k (TyFun a6989586621679072651 (First a6989586621679072651) -> Type) -> Type) | |
type Apply (Let6989586621680451197Scrutinee_6989586621680450978Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) Any -> Type) -> Type) (p6989586621680451195 :: a6989586621680450730 ~> Bool) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Let6989586621680451197Scrutinee_6989586621680450978Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) Any -> Type) -> Type) (p6989586621680451195 :: a6989586621680450730 ~> Bool) = (Let6989586621680451197Scrutinee_6989586621680450978Sym1 p6989586621680451195 :: TyFun (t6989586621680450727 a6989586621680450730) Any -> Type) | |
type Apply (Let6989586621680451184Scrutinee_6989586621680450980Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) All -> Type) -> Type) (p6989586621680451182 :: a6989586621680450730 ~> Bool) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Let6989586621680451184Scrutinee_6989586621680450980Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) All -> Type) -> Type) (p6989586621680451182 :: a6989586621680450730 ~> Bool) = (Let6989586621680451184Scrutinee_6989586621680450980Sym1 p6989586621680451182 :: TyFun (t6989586621680450727 a6989586621680450730) All -> Type) | |
type Apply (Let6989586621680451099Scrutinee_6989586621680450986Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) (First a6989586621680450730) -> Type) -> Type) (p6989586621680451097 :: a6989586621680450730 ~> Bool) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Let6989586621680451099Scrutinee_6989586621680450986Sym0 :: TyFun (a6989586621680450730 ~> Bool) (TyFun (t6989586621680450727 a6989586621680450730) (First a6989586621680450730) -> Type) -> Type) (p6989586621680451097 :: a6989586621680450730 ~> Bool) = (Let6989586621680451099Scrutinee_6989586621680450986Sym1 p6989586621680451097 :: TyFun (t6989586621680450727 a6989586621680450730) (First a6989586621680450730) -> Type) | |
type Apply (Let6989586621679520515GoSym0 :: TyFun (k1 ~> Bool) (TyFun (k1 ~> k1) (TyFun k2 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (p6989586621679520512 :: k1 ~> Bool) | |
Defined in Data.Singletons.Prelude.Base | |
type Apply (FilterMSym0 :: TyFun (a6989586621681207798 ~> m6989586621681207797 Bool) ([a6989586621681207798] ~> m6989586621681207797 [a6989586621681207798]) -> Type) (a6989586621681208261 :: a6989586621681207798 ~> m6989586621681207797 Bool) | |
Defined in Data.Singletons.Prelude.Monad type Apply (FilterMSym0 :: TyFun (a6989586621681207798 ~> m6989586621681207797 Bool) ([a6989586621681207798] ~> m6989586621681207797 [a6989586621681207798]) -> Type) (a6989586621681208261 :: a6989586621681207798 ~> m6989586621681207797 Bool) = FilterMSym1 a6989586621681208261 | |
type Apply (AnySym0 :: TyFun (a6989586621680450646 ~> Bool) (t6989586621680450645 a6989586621680450646 ~> Bool) -> Type) (a6989586621680451191 :: a6989586621680450646 ~> Bool) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (AllSym0 :: TyFun (a6989586621680450644 ~> Bool) (t6989586621680450643 a6989586621680450644 ~> Bool) -> Type) (a6989586621680451178 :: a6989586621680450644 ~> Bool) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (FindSym0 :: TyFun (a6989586621680450636 ~> Bool) (t6989586621680450635 a6989586621680450636 ~> Maybe a6989586621680450636) -> Type) (a6989586621680451093 :: a6989586621680450636 ~> Bool) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FindSym0 :: TyFun (a6989586621680450636 ~> Bool) (t6989586621680450635 a6989586621680450636 ~> Maybe a6989586621680450636) -> Type) (a6989586621680451093 :: a6989586621680450636 ~> Bool) = (FindSym1 a6989586621680451093 t6989586621680450635 :: TyFun (t6989586621680450635 a6989586621680450636) (Maybe a6989586621680450636) -> Type) | |
type Apply (MfilterSym0 :: TyFun (a6989586621681207760 ~> Bool) (m6989586621681207759 a6989586621681207760 ~> m6989586621681207759 a6989586621681207760) -> Type) (a6989586621681208095 :: a6989586621681207760 ~> Bool) | |
Defined in Data.Singletons.Prelude.Monad type Apply (MfilterSym0 :: TyFun (a6989586621681207760 ~> Bool) (m6989586621681207759 a6989586621681207760 ~> m6989586621681207759 a6989586621681207760) -> Type) (a6989586621681208095 :: a6989586621681207760 ~> Bool) = (MfilterSym1 a6989586621681208095 m6989586621681207759 :: TyFun (m6989586621681207759 a6989586621681207760) (m6989586621681207759 a6989586621681207760) -> Type) | |
type Apply (TFHelper_6989586621680882853Sym0 :: TyFun (Arg a6989586621680881636 b6989586621680881637) (Arg a6989586621680881636 b6989586621680881637 ~> Bool) -> Type) (a6989586621680882851 :: Arg a6989586621680881636 b6989586621680881637) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679948941 :: k1 ~> (k1 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679948953Scrutinee_6989586621679940376Sym0 :: TyFun (k1 ~> (k1 ~> Bool)) (TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679948941 :: k1 ~> (k1 ~> Bool)) = (Let6989586621679948953Scrutinee_6989586621679940376Sym1 eq6989586621679948941 :: TyFun k2 (TyFun k1 (TyFun k3 (TyFun [k1] Bool -> Type) -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679950280Scrutinee_6989586621679940348Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (p6989586621679950274 :: k1 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679950280Scrutinee_6989586621679940348Sym0 :: TyFun (k1 ~> Bool) (TyFun k1 (TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) -> Type) -> Type) (p6989586621679950274 :: k1 ~> Bool) = (Let6989586621679950280Scrutinee_6989586621679940348Sym1 p6989586621679950274 :: TyFun k1 (TyFun [a6989586621679939789] (TyFun k Bool -> Type) -> Type) -> Type) | |
type Apply (Lambda_6989586621681208101Sym0 :: TyFun (k1 ~> Bool) (TyFun k (TyFun k1 (m6989586621679544699 k1) -> Type) -> Type) -> Type) (p6989586621681208099 :: k1 ~> Bool) | |
Defined in Data.Singletons.Prelude.Monad | |
type Apply (Lambda_6989586621681208269Sym0 :: TyFun (k2 ~> f6989586621679544675 Bool) (TyFun k3 (TyFun k2 (TyFun (f6989586621679544675 [k2]) (f6989586621679544675 [k2]) -> Type) -> Type) -> Type) -> Type) (p6989586621681208267 :: k2 ~> f6989586621679544675 Bool) | |
Defined in Data.Singletons.Prelude.Monad type Apply (Lambda_6989586621681208269Sym0 :: TyFun (k2 ~> f6989586621679544675 Bool) (TyFun k3 (TyFun k2 (TyFun (f6989586621679544675 [k2]) (f6989586621679544675 [k2]) -> Type) -> Type) -> Type) -> Type) (p6989586621681208267 :: k2 ~> f6989586621679544675 Bool) = (Lambda_6989586621681208269Sym1 p6989586621681208267 :: TyFun k3 (TyFun k2 (TyFun (f6989586621679544675 [k2]) (f6989586621679544675 [k2]) -> Type) -> Type) -> Type) | |
type Apply (Lambda_6989586621679949935Sym0 :: TyFun (b6989586621679544703 ~> (a6989586621679939772 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939772 (TyFun [a6989586621679939772] (TyFun b6989586621679544703 (m6989586621679544699 b6989586621679544703) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679949919 :: b6989586621679544703 ~> (a6989586621679939772 ~> Bool)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Lambda_6989586621679949935Sym0 :: TyFun (b6989586621679544703 ~> (a6989586621679939772 ~> Bool)) (TyFun k1 (TyFun k2 (TyFun a6989586621679939772 (TyFun [a6989586621679939772] (TyFun b6989586621679544703 (m6989586621679544699 b6989586621679544703) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (eq6989586621679949919 :: b6989586621679544703 ~> (a6989586621679939772 ~> Bool)) = (Lambda_6989586621679949935Sym1 eq6989586621679949919 :: TyFun k1 (TyFun k2 (TyFun a6989586621679939772 (TyFun [a6989586621679939772] (TyFun b6989586621679544703 (m6989586621679544699 b6989586621679544703) -> Type) -> Type) -> Type) -> Type) -> Type) |
The character type Char
is an enumeration whose values represent
Unicode (or equivalently ISO/IEC 10646) code points (i.e. characters, see
http://www.unicode.org/ for details). This set extends the ISO 8859-1
(Latin-1) character set (the first 256 characters), which is itself an extension
of the ASCII character set (the first 128 characters). A character literal in
Haskell has type Char
.
To convert a Char
to or from the corresponding Int
value defined
by Unicode, use toEnum
and fromEnum
from the
Enum
class respectively (or equivalently ord
and chr
).
Instances
Double-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE double-precision type.
Instances
Single-precision floating point numbers. It is desirable that this type be at least equal in range and precision to the IEEE single-precision type.
Instances
A fixed-precision integer type with at least the range [-2^29 .. 2^29-1]
.
The exact range for a given implementation can be determined by using
minBound
and maxBound
from the Bounded
class.
Instances
Invariant: Jn#
and Jp#
are used iff value doesn't fit in S#
Useful properties resulting from the invariants:
Instances
Enum Integer | Since: base-2.1 |
Eq Integer | |
Integral Integer | Since: base-2.0.1 |
Defined in GHC.Real | |
Data Integer | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Integer -> c Integer # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Integer # toConstr :: Integer -> Constr # dataTypeOf :: Integer -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Integer) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Integer) # gmapT :: (forall b. Data b => b -> b) -> Integer -> Integer # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Integer -> r # gmapQ :: (forall d. Data d => d -> u) -> Integer -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Integer -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Integer -> m Integer # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Integer -> m Integer # | |
Num Integer | Since: base-2.1 |
Ord Integer | |
Read Integer | Since: base-2.1 |
Real Integer | Since: base-2.0.1 |
Defined in GHC.Real Methods toRational :: Integer -> Rational # | |
Show Integer | Since: base-2.1 |
Ix Integer | Since: base-2.1 |
Defined in GHC.Arr | |
Lift Integer | |
Random Integer | |
Defined in System.Random | |
NFData Integer | |
Defined in Control.DeepSeq | |
Hashable Integer | |
Defined in Data.Hashable.Class | |
ToJSON Integer | |
Defined in Data.Aeson.Types.ToJSON | |
ToJSONKey Integer | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON Integer | This instance includes a bounds check to prevent maliciously
large inputs to fill up the memory of the target system. You can
newtype |
FromJSONKey Integer | |
Defined in Data.Aeson.Types.FromJSON Methods | |
UniqueFactorisation Integer | |
PrintfArg Integer | Since: base-2.1 |
Defined in Text.Printf | |
Default Integer | |
Defined in Data.Default.Class | |
CRandomR Integer | |
Defined in Control.Monad.CryptoRandom | |
C Integer | |
C Integer | |
Defined in Algebra.ToInteger | |
C Integer | |
C Integer | |
Defined in Algebra.ToRational Methods toRational :: Integer -> Rational # | |
C Integer | |
C Integer | |
C Integer | |
C Integer | |
C Integer | |
C Integer | |
Defined in Algebra.ZeroTestable | |
C Integer | |
CRTEmbed Integer Source # | Embeds into the complex numbers \(\C\). (May not have sufficient precision.) |
C Integer Integer | |
CRTrans Maybe Integer Source # | Returns |
KnownNat n => Reifies (n :: Nat) Integer | |
Defined in Data.Reflection | |
() :=> (Enum Integer) | |
() :=> (Eq Integer) | |
() :=> (Integral Integer) | |
() :=> (Num Integer) | |
() :=> (Ord Integer) | |
() :=> (Real Integer) | |
() :=> (Bits Integer) | |
C a => C Integer (T a) | |
(Reflects q z, ToInteger z) => Reduce Integer (ZqBasic q z) Source # | |
Foldable (t m) => FoldableCyc (Cyc t m) Integer Source # | |
Functor (t m) => FunctorCyc (Cyc t m) Integer Integer Source # | |
(Fact m, Functor (t m), UnCyc t Int64) => FunctorCyc (Cyc t m) Int64 Integer Source # | |
(Fact m, Functor (t m), UnCyc t Double) => FunctorCyc (Cyc t m) Double Integer Source # | |
(Fact m, Functor (t m), UnCyc t (a, b)) => FunctorCyc (Cyc t m) (a, b) Integer Source # | |
(Fact m, Functor (t m), UnCyc t (ZqBasic q z)) => FunctorCyc (Cyc t m) (ZqBasic q z) Integer Source # | |
(Fact m, Functor (t m), UnCyc t (RRq q r)) => FunctorCyc (Cyc t m) (RRq q r) Integer Source # | |
Show (t m Integer) => Show (Cyc t m Integer) Source # | |
(Random (t m Integer), Fact m) => Random (Cyc t m Integer) Source # | |
Defined in Crypto.Lol.Cyclotomic.Cyc Methods randomR :: RandomGen g => (Cyc t m Integer, Cyc t m Integer) -> g -> (Cyc t m Integer, g) # random :: RandomGen g => g -> (Cyc t m Integer, g) # randomRs :: RandomGen g => (Cyc t m Integer, Cyc t m Integer) -> g -> [Cyc t m Integer] # randoms :: RandomGen g => g -> [Cyc t m Integer] # randomRIO :: (Cyc t m Integer, Cyc t m Integer) -> IO (Cyc t m Integer) # | |
(Fact m, forall (m' :: Factored). Fact m' => NFData (t m' Integer)) => NFData (Cyc t m Integer) Source # | |
Defined in Crypto.Lol.Cyclotomic.Cyc | |
ZeroTestable (t m Integer) => C (Cyc t m Integer) Source # | |
(Reflects q Int64, Functor (t m)) => Reduce (Cyc t m Integer) (Cyc t m (ZqBasic q Int64)) Source # | |
type CRTExt Integer Source # | |
Defined in Crypto.Lol.CRTrans | |
data Cyc t m Integer Source # | cyclotomic ring of integers with unbounded precision, limited to powerful- or decoding-basis representation. |
The Maybe
type encapsulates an optional value. A value of type
either contains a value of type Maybe
aa
(represented as
),
or it is empty (represented as Just
aNothing
). Using Maybe
is a good way to
deal with errors or exceptional cases without resorting to drastic
measures such as error
.
The Maybe
type is also a monad. It is a simple kind of error
monad, where all errors are represented by Nothing
. A richer
error monad can be built using the Either
type.
Instances
Monad Maybe | Since: base-2.1 |
Functor Maybe | Since: base-2.1 |
MonadFix Maybe | Since: base-2.1 |
Defined in Control.Monad.Fix | |
Applicative Maybe | Since: base-2.1 |
Foldable Maybe | Since: base-2.1 |
Defined in Data.Foldable Methods fold :: Monoid m => Maybe m -> m # foldMap :: Monoid m => (a -> m) -> Maybe a -> m # foldr :: (a -> b -> b) -> b -> Maybe a -> b # foldr' :: (a -> b -> b) -> b -> Maybe a -> b # foldl :: (b -> a -> b) -> b -> Maybe a -> b # foldl' :: (b -> a -> b) -> b -> Maybe a -> b # foldr1 :: (a -> a -> a) -> Maybe a -> a # foldl1 :: (a -> a -> a) -> Maybe a -> a # elem :: Eq a => a -> Maybe a -> Bool # maximum :: Ord a => Maybe a -> a # minimum :: Ord a => Maybe a -> a # | |
Traversable Maybe | Since: base-2.1 |
MonadPlus Maybe | Since: base-2.1 |
ToJSON1 Maybe | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a -> Value) -> ([a] -> Value) -> Maybe a -> Value # liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Maybe a] -> Value # liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Maybe a -> Encoding # liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Maybe a] -> Encoding # | |
FromJSON1 Maybe | |
Alternative Maybe | Since: base-2.1 |
Eq1 Maybe | Since: base-4.9.0.0 |
Ord1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read1 Maybe | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Show1 Maybe | Since: base-4.9.0.0 |
NFData1 Maybe | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable1 Maybe | |
Defined in Data.Hashable.Class | |
ExtKey Maybe | |
PTraversable Maybe | |
STraversable Maybe | |
Defined in Data.Singletons.Prelude.Traversable Methods sTraverse :: SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply TraverseSym0 t1) t2) # sSequenceA :: SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 t1) # sMapM :: SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply MapMSym0 t1) t2) # sSequence :: SMonad m => Sing t1 -> Sing (Apply SequenceSym0 t1) # | |
PFoldable Maybe | |
SFoldable Maybe | |
Defined in Data.Singletons.Prelude.Foldable Methods sFold :: SMonoid m => Sing t1 -> Sing (Apply FoldSym0 t1) # sFoldMap :: SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 t1) t2) # sFoldr :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldrSym0 t1) t2) t3) # sFoldr' :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldr'Sym0 t1) t2) t3) # sFoldl :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldlSym0 t1) t2) t3) # sFoldl' :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldl'Sym0 t1) t2) t3) # sFoldr1 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) # sFoldl1 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) # sToList :: Sing t1 -> Sing (Apply ToListSym0 t1) # sNull :: Sing t1 -> Sing (Apply NullSym0 t1) # sLength :: Sing t1 -> Sing (Apply LengthSym0 t1) # sElem :: SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) # sMaximum :: SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) # sMinimum :: SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) # sSum :: SNum a => Sing t1 -> Sing (Apply SumSym0 t1) # sProduct :: SNum a => Sing t1 -> Sing (Apply ProductSym0 t1) # | |
PFunctor Maybe | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
PApplicative Maybe | |
PMonad Maybe | |
PAlternative Maybe | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
PMonadPlus Maybe | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
SFunctor Maybe | |
SApplicative Maybe | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods sPure :: Sing t -> Sing (Apply PureSym0 t) # (%<*>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*>@#@$) t1) t2) # sLiftA2 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply LiftA2Sym0 t1) t2) t3) # (%*>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (*>@#@$) t1) t2) # (%<*) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*@#@$) t1) t2) # | |
SMonad Maybe | |
SAlternative Maybe | |
SMonadPlus Maybe | |
MonadError () Maybe | Since: mtl-2.2.2 |
Defined in Control.Monad.Error.Class | |
CRTrans Maybe Double Source # | Returns |
CRTrans Maybe Int Source # | Returns |
CRTrans Maybe Int64 Source # | Returns |
CRTrans Maybe Integer Source # | Returns |
(Selector s, GToJSON enc arity (K1 i (Maybe a) :: Type -> Type), KeyValuePair enc pairs, Monoid pairs) => RecordToPairs enc pairs arity (S1 s (K1 i (Maybe a) :: Type -> Type)) | |
Defined in Data.Aeson.Types.ToJSON | |
() :=> (Functor Maybe) | |
() :=> (Applicative Maybe) | |
Defined in Data.Constraint Methods ins :: () :- Applicative Maybe # | |
() :=> (MonadPlus Maybe) | |
() :=> (Alternative Maybe) | |
Defined in Data.Constraint Methods ins :: () :- Alternative Maybe # | |
(Default a, Unbox a) => Vector Vector (Maybe a) Source # | |
Defined in Crypto.Lol.Prelude Methods basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (Maybe a) -> m (Vector (Maybe a)) # basicUnsafeThaw :: PrimMonad m => Vector (Maybe a) -> m (Mutable Vector (PrimState m) (Maybe a)) # basicLength :: Vector (Maybe a) -> Int # basicUnsafeSlice :: Int -> Int -> Vector (Maybe a) -> Vector (Maybe a) # basicUnsafeIndexM :: Monad m => Vector (Maybe a) -> Int -> m (Maybe a) # basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (Maybe a) -> Vector (Maybe a) -> m () # | |
(Default a, Unbox a) => MVector MVector (Maybe a) Source # | |
Defined in Crypto.Lol.Prelude Methods basicLength :: MVector s (Maybe a) -> Int # basicUnsafeSlice :: Int -> Int -> MVector s (Maybe a) -> MVector s (Maybe a) # basicOverlaps :: MVector s (Maybe a) -> MVector s (Maybe a) -> Bool # basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (Maybe a)) # basicInitialize :: PrimMonad m => MVector (PrimState m) (Maybe a) -> m () # basicUnsafeReplicate :: PrimMonad m => Int -> Maybe a -> m (MVector (PrimState m) (Maybe a)) # basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (Maybe a) -> Int -> m (Maybe a) # basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (Maybe a) -> Int -> Maybe a -> m () # basicClear :: PrimMonad m => MVector (PrimState m) (Maybe a) -> m () # basicSet :: PrimMonad m => MVector (PrimState m) (Maybe a) -> Maybe a -> m () # basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (Maybe a) -> MVector (PrimState m) (Maybe a) -> m () # basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (Maybe a) -> MVector (PrimState m) (Maybe a) -> m () # basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (Maybe a) -> Int -> m (MVector (PrimState m) (Maybe a)) # | |
Transcendental a => CRTrans Maybe (Complex a) Source # | For testing ergonomics, we also have a |
(Default msg, Default a) => MessageAPI msg (msg -> Maybe a) a | |
(Reflects q z, ToInteger z, PID z, Enum z, NFData z) => CRTrans Maybe (ZqBasic q z) Source # | |
(GFCtx fp d, NFData fp) => CRTrans Maybe (GF fp d) Source # | |
(Selector s, FromJSON a) => RecordFromJSON arity (S1 s (K1 i (Maybe a) :: Type -> Type)) | |
Defined in Data.Aeson.Types.FromJSON | |
Default v => MessageAPI msg (Key Maybe msg v) v | |
Eq a => Eq (Maybe a) | Since: base-2.1 |
Data a => Data (Maybe a) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe a -> c (Maybe a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe a) # toConstr :: Maybe a -> Constr # dataTypeOf :: Maybe a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe a)) # gmapT :: (forall b. Data b => b -> b) -> Maybe a -> Maybe a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe a -> r # gmapQ :: (forall d. Data d => d -> u) -> Maybe a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe a -> m (Maybe a) # | |
Ord a => Ord (Maybe a) | Since: base-2.1 |
Read a => Read (Maybe a) | Since: base-2.1 |
Show a => Show (Maybe a) | Since: base-2.1 |
Generic (Maybe a) | |
Semigroup a => Semigroup (Maybe a) | Since: base-4.9.0.0 |
Semigroup a => Monoid (Maybe a) | Lift a semigroup into Since 4.11.0: constraint on inner Since: base-2.1 |
Lift a => Lift (Maybe a) | |
Testable prop => Testable (Maybe prop) | |
NFData a => NFData (Maybe a) | |
Defined in Control.DeepSeq | |
Hashable a => Hashable (Maybe a) | |
Defined in Data.Hashable.Class | |
ToJSON a => ToJSON (Maybe a) | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON a => FromJSON (Maybe a) | |
SingKind a => SingKind (Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
Default (Maybe a) | |
Defined in Data.Default.Class | |
TextType a => TextType (Maybe a) | |
Mergeable a => Mergeable (Maybe a) | |
Defined in Text.ProtocolBuffers.Basic Methods mergeAppend :: Maybe a -> Maybe a -> Maybe a # mergeConcat :: Foldable t => t (Maybe a) -> Maybe a # | |
Default (Maybe a) | |
Defined in Text.ProtocolBuffers.Basic Methods defaultValue :: Maybe a # | |
PMonoid (Maybe a) | |
SSemigroup a => SMonoid (Maybe a) | |
Defined in Data.Singletons.Prelude.Monoid | |
PShow (Maybe a) | |
SShow a => SShow (Maybe a) | |
PSemigroup (Maybe a) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
SSemigroup a => SSemigroup (Maybe a) | |
POrd (Maybe a) | |
SOrd a => SOrd (Maybe a) | |
Defined in Data.Singletons.Prelude.Ord Methods sCompare :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) # (%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) # (%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) # (%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) # (%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) # sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) # sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) # | |
SEq a => SEq (Maybe a) | |
PEq (Maybe a) | |
(Default a, Unbox a) => Unbox (Maybe a) Source # | |
Defined in Crypto.Lol.Prelude | |
Generic1 Maybe | |
SingI (Nothing :: Maybe a) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
(Eq a) :=> (Eq (Maybe a)) | |
(Ord a) :=> (Ord (Maybe a)) | |
(Read a) :=> (Read (Maybe a)) | |
(Show a) :=> (Show (Maybe a)) | |
(Semigroup a) :=> (Semigroup (Maybe a)) | |
(Monoid a) :=> (Monoid (Maybe a)) | |
SingI a2 => SingI (Just a2 :: Maybe a1) | Since: base-4.9.0.0 |
Defined in GHC.Generics | |
SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a6989586621679495141] [a6989586621679495141] -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a6989586621679495142] (Maybe a6989586621679495142) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a6989586621680065917] ([a6989586621680065917] ~> Maybe [a6989586621680065917]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679608129Sym0 :: TyFun (Maybe a6989586621679544754) (Maybe a6989586621679544754 ~> Maybe a6989586621679544754) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a6989586621679495143) [a6989586621679495143] -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a6989586621679495146) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a6989586621679495147) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a6989586621679495145) a6989586621679495145 -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MinInternalSym0 :: TyFun (Maybe a6989586621680441747) (MinInternal a6989586621680441747) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MaxInternalSym0 :: TyFun (Maybe a6989586621680441068) (MaxInternal a6989586621680441068) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390863Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (OptionSym0 :: TyFun (Maybe a6989586621679051026) (Option a6989586621679051026) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (LastSym0 :: TyFun (Maybe a6989586621679072646) (Last a6989586621679072646) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FirstSym0 :: TyFun (Maybe a6989586621679072651) (First a6989586621679072651) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680280853Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Fail_6989586621679608036Sym0 :: TyFun Symbol (Maybe a6989586621679544705) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Pure_6989586621679607829Sym0 :: TyFun a6989586621679544676 (Maybe a6989586621679544676) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679608125LSym0 :: TyFun k1 (Maybe k1) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a6989586621679495144 (Maybe a6989586621679495144 ~> a6989586621679495144) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a6989586621679939701 ([a6989586621679939701] ~> Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (JustSym0 :: TyFun a3530822107858468865 (Maybe a3530822107858468865) -> Type) | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (GetOptionSym0 :: TyFun (Option a6989586621679051026) (Maybe a6989586621679051026) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (GetFirstSym0 :: TyFun (First a6989586621679072651) (Maybe a6989586621679072651) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (GetLastSym0 :: TyFun (Last a6989586621679072646) (Maybe a6989586621679072646) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621679939702 ~> Bool) ([a6989586621679939702] ~> Maybe a6989586621679939702) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a6989586621679939699 ~> Bool) ([a6989586621679939699] ~> Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SingI (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing CatMaybesSym0 # | |
SingI (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing ListToMaybeSym0 # | |
SingI (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing MaybeToListSym0 # | |
SingI (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing IsNothingSym0 # | |
SingI (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing IsJustSym0 # | |
SingI (FromJustSym0 :: TyFun (Maybe a) a -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing FromJustSym0 # | |
SingI (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods sing :: Sing OptionSym0 # | |
SingI (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid | |
SingI (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid | |
SingI (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing FromMaybeSym0 # | |
SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing ElemIndexSym0 # | |
SingI (JustSym0 :: TyFun a (Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.Instances | |
SingI (FindSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing FindIndexSym0 # | |
SuppressUnusedWarnings (StripPrefixSym1 a6989586621680078627 :: TyFun [a6989586621680065917] (Maybe [a6989586621680065917]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindSym1 a6989586621679949259 :: TyFun [a6989586621679939702] (Maybe a6989586621679939702) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindIndexSym1 a6989586621679949619 :: TyFun [a6989586621679939699] (Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ElemIndexSym1 a6989586621679949627 :: TyFun [a6989586621679939701] (Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679608129Sym1 a6989586621679608127 :: TyFun (Maybe a6989586621679544754) (Maybe a6989586621679544754) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679608029Sym0 :: TyFun (Maybe a6989586621679544702) (Maybe b6989586621679544703 ~> Maybe b6989586621679544703) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679608013Sym0 :: TyFun (Maybe a6989586621679544700) ((a6989586621679544700 ~> Maybe b6989586621679544701) ~> Maybe b6989586621679544701) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679607871Sym0 :: TyFun (Maybe a6989586621679544682) (Maybe b6989586621679544683 ~> Maybe b6989586621679544683) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FromMaybeSym1 a6989586621679495336 :: TyFun (Maybe a6989586621679495144) a6989586621679495144 -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680280853Sym1 a6989586621680280850 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390863Sym1 a6989586621679390861 :: TyFun (Maybe a3530822107858468865) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679607841Sym0 :: TyFun (Maybe (a6989586621679544677 ~> b6989586621679544678)) (Maybe a6989586621679544677 ~> Maybe b6989586621679544678) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679607700Sym0 :: TyFun a6989586621679544673 (Maybe b6989586621679544674 ~> Maybe a6989586621679544673) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b6989586621679493717 ((a6989586621679493718 ~> b6989586621679493717) ~> (Maybe a6989586621679493718 ~> b6989586621679493717)) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (LookupSym0 :: TyFun a6989586621679939680 ([(a6989586621679939680, b6989586621679939681)] ~> Maybe b6989586621679939681) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442545NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442545MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442518NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442518MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (OptionalSym0 :: TyFun (f6989586621681199025 a6989586621681199026) (f6989586621681199025 (Maybe a6989586621681199026)) -> Type) | |
Defined in Data.Singletons.Prelude.Applicative Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Fmap_6989586621679607680Sym0 :: TyFun (a6989586621679544671 ~> b6989586621679544672) (Maybe a6989586621679544671 ~> Maybe b6989586621679544672) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (a6989586621679495139 ~> Maybe b6989586621679495140) ([a6989586621679495139] ~> [b6989586621679495140]) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b6989586621679939758 ~> Maybe (a6989586621679939759, b6989586621679939758)) (b6989586621679939758 ~> [a6989586621679939759]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindSym0 :: TyFun (a6989586621680450636 ~> Bool) (t6989586621680450635 a6989586621680450636 ~> Maybe a6989586621680450636) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SingI d => SingI (FindSym1 d :: TyFun [a] (Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (FindIndexSym1 d) # | |
(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Nat) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (ElemIndexSym1 d) # | |
SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing (FromMaybeSym1 d) # | |
SingI (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing Maybe_Sym0 # | |
SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing LookupSym0 # | |
SAlternative f => SingI (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) | |
Defined in Data.Singletons.Prelude.Applicative Methods sing :: Sing OptionalSym0 # | |
SingI (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing MapMaybeSym0 # | |
SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing UnfoldrSym0 # | |
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SuppressUnusedWarnings (LookupSym1 a6989586621679949041 b6989586621679939681 :: TyFun [(a6989586621679939680, b6989586621679939681)] (Maybe b6989586621679939681) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679608029Sym1 a6989586621679608027 b6989586621679544703 :: TyFun (Maybe b6989586621679544703) (Maybe b6989586621679544703) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679607871Sym1 a6989586621679607869 b6989586621679544683 :: TyFun (Maybe b6989586621679544683) (Maybe b6989586621679544683) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679607841Sym1 a6989586621679607839 :: TyFun (Maybe a6989586621679544677) (Maybe b6989586621679544678) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679607700Sym1 a6989586621679607698 b6989586621679544674 :: TyFun (Maybe b6989586621679544674) (Maybe a6989586621679544673) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Fmap_6989586621679607680Sym1 a6989586621679607678 :: TyFun (Maybe a6989586621679544671) (Maybe b6989586621679544672) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442545NSym1 x6989586621680442543 :: TyFun k1 (Maybe k1) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442545MSym1 x6989586621680442543 :: TyFun k (Maybe k1) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442518NSym1 x6989586621680442516 :: TyFun k1 (Maybe k1) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680442518MSym1 x6989586621680442516 :: TyFun k (Maybe k1) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (FindSym1 a6989586621680451093 t6989586621680450635 :: TyFun (t6989586621680450635 a6989586621680450636) (Maybe a6989586621680450636) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680338899Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680338811Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Traverse_6989586621680754401Sym0 :: TyFun (a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (Maybe a6989586621680748240 ~> f6989586621680748239 (Maybe b6989586621680748241)) -> Type) | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679608013Sym1 a6989586621679608011 b6989586621679544701 :: TyFun (a6989586621679544700 ~> Maybe b6989586621679544701) (Maybe b6989586621679544701) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (LiftA2_6989586621679607857Sym0 :: TyFun (a6989586621679544679 ~> (b6989586621679544680 ~> c6989586621679544681)) (Maybe a6989586621679544679 ~> (Maybe b6989586621679544680 ~> Maybe c6989586621679544681)) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Maybe_Sym1 a6989586621679493735 a6989586621679493718 :: TyFun (a6989586621679493718 ~> b6989586621679493717) (Maybe a6989586621679493718 ~> b6989586621679493717) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679495313RsSym0 :: TyFun (a6989586621679495139 ~> Maybe k1) (TyFun k (TyFun [a6989586621679495139] [k1] -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451570MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451545MfSym0 :: TyFun (k3 ~> (k2 ~> k3)) (TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
(SEq a, SingI d) => SingI (LookupSym1 d b :: TyFun [(a, b)] (Maybe b) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing (LookupSym1 d b) # | |
(SFoldable t, SingI d) => SingI (FindSym1 d t :: TyFun (t a) (Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable | |
SingI d => SingI (Maybe_Sym1 d a :: TyFun (a ~> b) (Maybe a ~> b) -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing (Maybe_Sym1 d a) # | |
SuppressUnusedWarnings (Traverse_6989586621680754401Sym1 a6989586621680754399 :: TyFun (Maybe a6989586621680748240) (f6989586621680748239 (Maybe b6989586621680748241)) -> Type) | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (LiftA2_6989586621679607857Sym1 a6989586621679607854 :: TyFun (Maybe a6989586621679544679) (Maybe b6989586621679544680 ~> Maybe c6989586621679544681) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Maybe_Sym2 a6989586621679493736 a6989586621679493735 :: TyFun (Maybe a6989586621679493718) b6989586621679493717 -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451570MfSym1 f6989586621680451568 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451545MfSym1 f6989586621680451543 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680338899Sym1 a6989586621680338897 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680338811Sym1 a6989586621680338809 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
(SingI d1, SingI d2) => SingI (Maybe_Sym2 d1 d2 :: TyFun (Maybe a) b -> Type) | |
Defined in Data.Singletons.Prelude.Maybe Methods sing :: Sing (Maybe_Sym2 d1 d2) # | |
SuppressUnusedWarnings (LiftA2_6989586621679607857Sym2 a6989586621679607855 a6989586621679607854 :: TyFun (Maybe b6989586621679544680) (Maybe c6989586621679544681) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451570MfSym2 xs6989586621680451569 f6989586621680451568 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451545MfSym2 xs6989586621680451544 f6989586621680451543 :: TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680338899Sym2 k6989586621680338898 a6989586621680338897 :: TyFun k1 (Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Lambda_6989586621680338811Sym2 k6989586621680338810 a6989586621680338809 :: TyFun k1 (Maybe a) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451545MfSym3 a6989586621680451546 xs6989586621680451544 f6989586621680451543 :: TyFun (Maybe k2) (Maybe k3) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451570MfSym3 a6989586621680451571 xs6989586621680451569 f6989586621680451568 :: TyFun k3 (Maybe k3) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
type Empty | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Mzero | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Product (arg :: Maybe a) | |
type Sum (arg :: Maybe a) | |
type Minimum (arg :: Maybe a) | |
type Maximum (arg :: Maybe a) | |
type Length (arg :: Maybe a) | |
type Null (arg :: Maybe a) | |
type ToList (arg :: Maybe a) | |
type Fold (arg :: Maybe m) | |
type Pure (a :: k1) | |
type Fail a2 | |
type Return (arg :: a) | |
type Sequence (arg :: Maybe (m a)) | |
type SequenceA (arg :: Maybe (f a)) | |
type Elem (arg1 :: a) (arg2 :: Maybe a) | |
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) | |
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) | |
type (a1 :: Maybe a6989586621679544754) <|> (a2 :: Maybe a6989586621679544754) | |
type Mplus (arg1 :: Maybe a) (arg2 :: Maybe a) | |
type FoldMap (a1 :: a6989586621680450730 ~> k2) (a2 :: Maybe a6989586621680450730) | |
type (a1 :: k1) <$ (a2 :: Maybe b6989586621679544674) | |
type Fmap (a1 :: a6989586621679544671 ~> b6989586621679544672) (a2 :: Maybe a6989586621679544671) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type (arg1 :: Maybe a) <* (arg2 :: Maybe b) | |
type (a1 :: Maybe a6989586621679544682) *> (a2 :: Maybe b6989586621679544683) | |
type (a1 :: Maybe (a6989586621679544677 ~> b6989586621679544678)) <*> (a2 :: Maybe a6989586621679544677) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type (a1 :: Maybe a6989586621679544702) >> (a2 :: Maybe b6989586621679544703) | |
type (a1 :: Maybe a6989586621679544700) >>= (a2 :: a6989586621679544700 ~> Maybe b6989586621679544701) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type MapM (arg1 :: a ~> m b) (arg2 :: Maybe a) | |
type Traverse (a1 :: a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (a2 :: Maybe a6989586621680748240) | |
Defined in Data.Singletons.Prelude.Traversable type Traverse (a1 :: a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (a2 :: Maybe a6989586621680748240) = Apply (Apply (Traverse_6989586621680754401Sym0 :: TyFun (a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (Maybe a6989586621680748240 ~> f6989586621680748239 (Maybe b6989586621680748241)) -> Type) a1) a2 | |
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) | |
type Foldl (a1 :: k2 ~> (a6989586621680450736 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450736) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Maybe a) | |
type Foldr (a1 :: a6989586621680450731 ~> (k2 ~> k2)) (a2 :: k2) (a3 :: Maybe a6989586621680450731) | |
Defined in Data.Singletons.Prelude.Foldable | |
type LiftA2 (a1 :: a6989586621679544679 ~> (b6989586621679544680 ~> c6989586621679544681)) (a2 :: Maybe a6989586621679544679) (a3 :: Maybe b6989586621679544680) | |
Defined in Data.Singletons.Prelude.Monad.Internal type LiftA2 (a1 :: a6989586621679544679 ~> (b6989586621679544680 ~> c6989586621679544681)) (a2 :: Maybe a6989586621679544679) (a3 :: Maybe b6989586621679544680) = Apply (Apply (Apply (LiftA2_6989586621679607857Sym0 :: TyFun (a6989586621679544679 ~> (b6989586621679544680 ~> c6989586621679544681)) (Maybe a6989586621679544679 ~> (Maybe b6989586621679544680 ~> Maybe c6989586621679544681)) -> Type) a1) a2) a3 | |
newtype MVector s (Maybe a) Source # | |
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679495349 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Maybe | |
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679495351 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Maybe | |
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679495346 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Maybe | |
type Apply (Compare_6989586621679390863Sym1 a6989586621679390861 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679390862 :: Maybe a) | |
type Apply (FromMaybeSym1 a6989586621679495336 :: TyFun (Maybe a) a -> Type) (a6989586621679495337 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Maybe | |
type Apply (Maybe_Sym2 a6989586621679493736 a6989586621679493735 :: TyFun (Maybe a) b -> Type) (a6989586621679493737 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Maybe | |
type Rep (Maybe a) | Since: base-4.6.0.0 |
data Sing (b :: Maybe a) | |
type DemoteRep (Maybe a) | |
Defined in GHC.Generics | |
type Mempty | |
Defined in Data.Singletons.Prelude.Monoid | |
data Sing (b :: Maybe a) | |
type Demote (Maybe a) | |
Defined in Data.Singletons.Prelude.Instances | |
newtype Vector (Maybe a) Source # | |
type Rep1 Maybe | Since: base-4.6.0.0 |
type Mconcat (arg :: [Maybe a]) | |
type Show_ (arg :: Maybe a) | |
type Sconcat (arg :: NonEmpty (Maybe a)) | |
type Mappend (arg1 :: Maybe a) (arg2 :: Maybe a) | |
type ShowList (arg1 :: [Maybe a]) arg2 | |
type (a2 :: Maybe a1) <> (a3 :: Maybe a1) | |
type Min (arg1 :: Maybe a) (arg2 :: Maybe a) | |
type Max (arg1 :: Maybe a) (arg2 :: Maybe a) | |
type (arg1 :: Maybe a) >= (arg2 :: Maybe a) | |
type (arg1 :: Maybe a) > (arg2 :: Maybe a) | |
type (arg1 :: Maybe a) <= (arg2 :: Maybe a) | |
type (arg1 :: Maybe a) < (arg2 :: Maybe a) | |
type Compare (a2 :: Maybe a1) (a3 :: Maybe a1) | |
type (x :: Maybe a) /= (y :: Maybe a) | |
type (a2 :: Maybe a1) == (b :: Maybe a1) | |
Defined in Data.Singletons.Prelude.Eq | |
type ShowsPrec a2 (a3 :: Maybe a1) a4 | |
type Apply (Pure_6989586621679607829Sym0 :: TyFun a (Maybe a) -> Type) (a6989586621679607828 :: a) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (Fail_6989586621679608036Sym0 :: TyFun Symbol (Maybe a6989586621679544705) -> Type) (a6989586621679608035 :: Symbol) | |
type Apply (Let6989586621679608125LSym0 :: TyFun k1 (Maybe k1) -> Type) (wild_69895866216796072866989586621679608124 :: k1) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (t6989586621679294580 :: a) | |
type Apply (Let6989586621680442518MSym1 x6989586621680442516 :: TyFun k (Maybe k1) -> Type) (y6989586621680442517 :: k) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Let6989586621680442518NSym1 x6989586621680442516 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680442517 :: k1) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Let6989586621680442545MSym1 x6989586621680442543 :: TyFun k (Maybe k1) -> Type) (y6989586621680442544 :: k) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Let6989586621680442545NSym1 x6989586621680442543 :: TyFun k1 (Maybe k1) -> Type) (y6989586621680442544 :: k1) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (Lambda_6989586621680338811Sym2 k6989586621680338810 a6989586621680338809 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338822 :: k1) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (Lambda_6989586621680338899Sym2 k6989586621680338898 a6989586621680338897 :: TyFun k1 (Maybe a) -> Type) (t6989586621680338910 :: k1) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (Let6989586621680451570MfSym3 a6989586621680451571 xs6989586621680451569 f6989586621680451568 :: TyFun k3 (Maybe k3) -> Type) (a6989586621680451572 :: k3) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679495325 :: [Maybe a]) | |
Defined in Data.Singletons.Prelude.Maybe | |
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679495333 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Maybe type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679495333 :: Maybe a) = MaybeToList a6989586621679495333 | |
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679495330 :: [a]) | |
Defined in Data.Singletons.Prelude.Maybe type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679495330 :: [a]) = ListToMaybe a6989586621679495330 | |
type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679820170 :: Option a) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680332716 :: First a) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680332737 :: Last a) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621679820173 :: Maybe a) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (t6989586621680332719 :: Maybe a) | |
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (t6989586621680332740 :: Maybe a) | |
type Apply (MaxInternalSym0 :: TyFun (Maybe a) (MaxInternal a) -> Type) (t6989586621680441739 :: Maybe a) | |
type Apply (MinInternalSym0 :: TyFun (Maybe a) (MinInternal a) -> Type) (t6989586621680441939 :: Maybe a) | |
type Apply (StripPrefixSym1 a6989586621680078627 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078628 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym1 a6989586621680078627 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621680078628 :: [a]) = StripPrefix a6989586621680078627 a6989586621680078628 | |
type Apply (FindIndexSym1 a6989586621679949619 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949620 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (ElemIndexSym1 a6989586621679949627 :: TyFun [a] (Maybe Nat) -> Type) (a6989586621679949628 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (TFHelper_6989586621679608129Sym1 a6989586621679608127 :: TyFun (Maybe a) (Maybe a) -> Type) (a6989586621679608128 :: Maybe a) | |
type Apply (FindSym1 a6989586621679949259 :: TyFun [a] (Maybe a) -> Type) (a6989586621679949260 :: [a]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621681199065 :: f a) | |
Defined in Data.Singletons.Prelude.Applicative | |
type Apply (Fmap_6989586621679607680Sym1 a6989586621679607678 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607679 :: Maybe a) | |
type Apply (TFHelper_6989586621679607700Sym1 a6989586621679607698 b :: TyFun (Maybe b) (Maybe a) -> Type) (a6989586621679607699 :: Maybe b) | |
type Apply (TFHelper_6989586621679607841Sym1 a6989586621679607839 :: TyFun (Maybe a) (Maybe b) -> Type) (a6989586621679607840 :: Maybe a) | |
type Apply (TFHelper_6989586621679607871Sym1 a6989586621679607869 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679607870 :: Maybe b) | |
type Apply (TFHelper_6989586621679608029Sym1 a6989586621679608027 b :: TyFun (Maybe b) (Maybe b) -> Type) (a6989586621679608028 :: Maybe b) | |
type Apply (LookupSym1 a6989586621679949041 b :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679949042 :: [(a, b)]) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (FindSym1 a6989586621680451093 t :: TyFun (t a) (Maybe a) -> Type) (a6989586621680451094 :: t a) | |
type Apply (Traverse_6989586621680754401Sym1 a6989586621680754399 :: TyFun (Maybe a) (f (Maybe b)) -> Type) (a6989586621680754400 :: Maybe a) | |
type Apply (LiftA2_6989586621679607857Sym2 a6989586621679607855 a6989586621679607854 :: TyFun (Maybe b) (Maybe c) -> Type) (a6989586621679607856 :: Maybe b) | |
type Apply (Let6989586621680451545MfSym3 a6989586621680451546 xs6989586621680451544 f6989586621680451543 :: TyFun (Maybe k2) (Maybe k3) -> Type) (a6989586621680451547 :: Maybe k2) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (TFHelper_6989586621679608013Sym1 a6989586621679608011 b :: TyFun (a ~> Maybe b) (Maybe b) -> Type) (a6989586621679608012 :: a ~> Maybe b) | |
type Apply (ElemIndexSym0 :: TyFun a6989586621679939701 ([a6989586621679939701] ~> Maybe Nat) -> Type) (a6989586621679949627 :: a6989586621679939701) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (ElemIndexSym0 :: TyFun a6989586621679939701 ([a6989586621679939701] ~> Maybe Nat) -> Type) (a6989586621679949627 :: a6989586621679939701) = ElemIndexSym1 a6989586621679949627 | |
type Apply (FromMaybeSym0 :: TyFun a6989586621679495144 (Maybe a6989586621679495144 ~> a6989586621679495144) -> Type) (a6989586621679495336 :: a6989586621679495144) | |
Defined in Data.Singletons.Prelude.Maybe type Apply (FromMaybeSym0 :: TyFun a6989586621679495144 (Maybe a6989586621679495144 ~> a6989586621679495144) -> Type) (a6989586621679495336 :: a6989586621679495144) = FromMaybeSym1 a6989586621679495336 | |
type Apply (ShowsPrec_6989586621680280853Sym0 :: TyFun Nat (Maybe a3530822107858468865 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680280850 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (Let6989586621680442518MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680442516 :: k1) | |
type Apply (Let6989586621680442518NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680442516 :: k) | |
type Apply (Let6989586621680442545MSym0 :: TyFun k1 (TyFun k (Maybe k1) -> Type) -> Type) (x6989586621680442543 :: k1) | |
type Apply (Let6989586621680442545NSym0 :: TyFun k (TyFun k1 (Maybe k1) -> Type) -> Type) (x6989586621680442543 :: k) | |
type Apply (LookupSym0 :: TyFun a6989586621679939680 ([(a6989586621679939680, b6989586621679939681)] ~> Maybe b6989586621679939681) -> Type) (a6989586621679949041 :: a6989586621679939680) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (LookupSym0 :: TyFun a6989586621679939680 ([(a6989586621679939680, b6989586621679939681)] ~> Maybe b6989586621679939681) -> Type) (a6989586621679949041 :: a6989586621679939680) = (LookupSym1 a6989586621679949041 b6989586621679939681 :: TyFun [(a6989586621679939680, b6989586621679939681)] (Maybe b6989586621679939681) -> Type) | |
type Apply (TFHelper_6989586621679607700Sym0 :: TyFun a6989586621679544673 (Maybe b6989586621679544674 ~> Maybe a6989586621679544673) -> Type) (a6989586621679607698 :: a6989586621679544673) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (TFHelper_6989586621679607700Sym0 :: TyFun a6989586621679544673 (Maybe b6989586621679544674 ~> Maybe a6989586621679544673) -> Type) (a6989586621679607698 :: a6989586621679544673) = (TFHelper_6989586621679607700Sym1 a6989586621679607698 b6989586621679544674 :: TyFun (Maybe b6989586621679544674) (Maybe a6989586621679544673) -> Type) | |
type Apply (Maybe_Sym0 :: TyFun b6989586621679493717 ((a6989586621679493718 ~> b6989586621679493717) ~> (Maybe a6989586621679493718 ~> b6989586621679493717)) -> Type) (a6989586621679493735 :: b6989586621679493717) | |
Defined in Data.Singletons.Prelude.Maybe type Apply (Maybe_Sym0 :: TyFun b6989586621679493717 ((a6989586621679493718 ~> b6989586621679493717) ~> (Maybe a6989586621679493718 ~> b6989586621679493717)) -> Type) (a6989586621679493735 :: b6989586621679493717) = (Maybe_Sym1 a6989586621679493735 a6989586621679493718 :: TyFun (a6989586621679493718 ~> b6989586621679493717) (Maybe a6989586621679493718 ~> b6989586621679493717) -> Type) | |
type Apply (Lambda_6989586621680338811Sym0 :: TyFun k (TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338809 :: k) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (Lambda_6989586621680338899Sym0 :: TyFun k (TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) -> Type) (a6989586621680338897 :: k) | |
Defined in Data.Singletons.Prelude.Monoid | |
type Apply (Let6989586621680451570MfSym1 f6989586621680451568 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451569 :: k) | |
type Apply (Let6989586621680451545MfSym1 f6989586621680451543 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) (xs6989586621680451544 :: k) | |
type Apply (Let6989586621680451545MfSym2 xs6989586621680451544 f6989586621680451543 :: TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) (a6989586621680451546 :: k3) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (StripPrefixSym0 :: TyFun [a6989586621680065917] ([a6989586621680065917] ~> Maybe [a6989586621680065917]) -> Type) (a6989586621680078627 :: [a6989586621680065917]) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (StripPrefixSym0 :: TyFun [a6989586621680065917] ([a6989586621680065917] ~> Maybe [a6989586621680065917]) -> Type) (a6989586621680078627 :: [a6989586621680065917]) = StripPrefixSym1 a6989586621680078627 | |
type Apply (TFHelper_6989586621679608129Sym0 :: TyFun (Maybe a6989586621679544754) (Maybe a6989586621679544754 ~> Maybe a6989586621679544754) -> Type) (a6989586621679608127 :: Maybe a6989586621679544754) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (Compare_6989586621679390863Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) (a6989586621679390861 :: Maybe a3530822107858468865) | |
type Apply (TFHelper_6989586621679607841Sym0 :: TyFun (Maybe (a6989586621679544677 ~> b6989586621679544678)) (Maybe a6989586621679544677 ~> Maybe b6989586621679544678) -> Type) (a6989586621679607839 :: Maybe (a6989586621679544677 ~> b6989586621679544678)) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (TFHelper_6989586621679607841Sym0 :: TyFun (Maybe (a6989586621679544677 ~> b6989586621679544678)) (Maybe a6989586621679544677 ~> Maybe b6989586621679544678) -> Type) (a6989586621679607839 :: Maybe (a6989586621679544677 ~> b6989586621679544678)) = TFHelper_6989586621679607841Sym1 a6989586621679607839 | |
type Apply (TFHelper_6989586621679607871Sym0 :: TyFun (Maybe a6989586621679544682) (Maybe b6989586621679544683 ~> Maybe b6989586621679544683) -> Type) (a6989586621679607869 :: Maybe a6989586621679544682) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (TFHelper_6989586621679607871Sym0 :: TyFun (Maybe a6989586621679544682) (Maybe b6989586621679544683 ~> Maybe b6989586621679544683) -> Type) (a6989586621679607869 :: Maybe a6989586621679544682) = (TFHelper_6989586621679607871Sym1 a6989586621679607869 b6989586621679544683 :: TyFun (Maybe b6989586621679544683) (Maybe b6989586621679544683) -> Type) | |
type Apply (TFHelper_6989586621679608029Sym0 :: TyFun (Maybe a6989586621679544702) (Maybe b6989586621679544703 ~> Maybe b6989586621679544703) -> Type) (a6989586621679608027 :: Maybe a6989586621679544702) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (TFHelper_6989586621679608029Sym0 :: TyFun (Maybe a6989586621679544702) (Maybe b6989586621679544703 ~> Maybe b6989586621679544703) -> Type) (a6989586621679608027 :: Maybe a6989586621679544702) = (TFHelper_6989586621679608029Sym1 a6989586621679608027 b6989586621679544703 :: TyFun (Maybe b6989586621679544703) (Maybe b6989586621679544703) -> Type) | |
type Apply (ShowsPrec_6989586621680280853Sym1 a6989586621680280850 a3530822107858468865 :: TyFun (Maybe a3530822107858468865) (Symbol ~> Symbol) -> Type) (a6989586621680280851 :: Maybe a3530822107858468865) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply (TFHelper_6989586621679608013Sym0 :: TyFun (Maybe a6989586621679544700) ((a6989586621679544700 ~> Maybe b6989586621679544701) ~> Maybe b6989586621679544701) -> Type) (a6989586621679608011 :: Maybe a6989586621679544700) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (TFHelper_6989586621679608013Sym0 :: TyFun (Maybe a6989586621679544700) ((a6989586621679544700 ~> Maybe b6989586621679544701) ~> Maybe b6989586621679544701) -> Type) (a6989586621679608011 :: Maybe a6989586621679544700) = (TFHelper_6989586621679608013Sym1 a6989586621679608011 b6989586621679544701 :: TyFun (a6989586621679544700 ~> Maybe b6989586621679544701) (Maybe b6989586621679544701) -> Type) | |
type Apply (LiftA2_6989586621679607857Sym1 a6989586621679607854 :: TyFun (Maybe a6989586621679544679) (Maybe b6989586621679544680 ~> Maybe c6989586621679544681) -> Type) (a6989586621679607855 :: Maybe a6989586621679544679) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (Let6989586621680451570MfSym2 xs6989586621680451569 f6989586621680451568 :: TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) (a6989586621680451571 :: Maybe k2) | |
Defined in Data.Singletons.Prelude.Foldable | |
type Apply (FindSym0 :: TyFun (a6989586621679939702 ~> Bool) ([a6989586621679939702] ~> Maybe a6989586621679939702) -> Type) (a6989586621679949259 :: a6989586621679939702 ~> Bool) | |
type Apply (FindIndexSym0 :: TyFun (a6989586621679939699 ~> Bool) ([a6989586621679939699] ~> Maybe Nat) -> Type) (a6989586621679949619 :: a6989586621679939699 ~> Bool) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (MapMaybeSym0 :: TyFun (a6989586621679495139 ~> Maybe b6989586621679495140) ([a6989586621679495139] ~> [b6989586621679495140]) -> Type) (a6989586621679495306 :: a6989586621679495139 ~> Maybe b6989586621679495140) | |
Defined in Data.Singletons.Prelude.Maybe type Apply (MapMaybeSym0 :: TyFun (a6989586621679495139 ~> Maybe b6989586621679495140) ([a6989586621679495139] ~> [b6989586621679495140]) -> Type) (a6989586621679495306 :: a6989586621679495139 ~> Maybe b6989586621679495140) = MapMaybeSym1 a6989586621679495306 | |
type Apply (Fmap_6989586621679607680Sym0 :: TyFun (a6989586621679544671 ~> b6989586621679544672) (Maybe a6989586621679544671 ~> Maybe b6989586621679544672) -> Type) (a6989586621679607678 :: a6989586621679544671 ~> b6989586621679544672) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type Apply (UnfoldrSym0 :: TyFun (b6989586621679939758 ~> Maybe (a6989586621679939759, b6989586621679939758)) (b6989586621679939758 ~> [a6989586621679939759]) -> Type) (a6989586621679949692 :: b6989586621679939758 ~> Maybe (a6989586621679939759, b6989586621679939758)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (UnfoldrSym0 :: TyFun (b6989586621679939758 ~> Maybe (a6989586621679939759, b6989586621679939758)) (b6989586621679939758 ~> [a6989586621679939759]) -> Type) (a6989586621679949692 :: b6989586621679939758 ~> Maybe (a6989586621679939759, b6989586621679939758)) = UnfoldrSym1 a6989586621679949692 | |
type Apply (FindSym0 :: TyFun (a6989586621680450636 ~> Bool) (t6989586621680450635 a6989586621680450636 ~> Maybe a6989586621680450636) -> Type) (a6989586621680451093 :: a6989586621680450636 ~> Bool) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (FindSym0 :: TyFun (a6989586621680450636 ~> Bool) (t6989586621680450635 a6989586621680450636 ~> Maybe a6989586621680450636) -> Type) (a6989586621680451093 :: a6989586621680450636 ~> Bool) = (FindSym1 a6989586621680451093 t6989586621680450635 :: TyFun (t6989586621680450635 a6989586621680450636) (Maybe a6989586621680450636) -> Type) | |
type Apply (Let6989586621679495313RsSym0 :: TyFun (a6989586621679495139 ~> Maybe k1) (TyFun k (TyFun [a6989586621679495139] [k1] -> Type) -> Type) -> Type) (f6989586621679495310 :: a6989586621679495139 ~> Maybe k1) | |
Defined in Data.Singletons.Prelude.Maybe type Apply (Let6989586621679495313RsSym0 :: TyFun (a6989586621679495139 ~> Maybe k1) (TyFun k (TyFun [a6989586621679495139] [k1] -> Type) -> Type) -> Type) (f6989586621679495310 :: a6989586621679495139 ~> Maybe k1) = (Let6989586621679495313RsSym1 f6989586621679495310 :: TyFun k (TyFun [a6989586621679495139] [k1] -> Type) -> Type) | |
type Apply (Let6989586621680451545MfSym0 :: TyFun (k3 ~> (k2 ~> k3)) (TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451543 :: k3 ~> (k2 ~> k3)) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Let6989586621680451545MfSym0 :: TyFun (k3 ~> (k2 ~> k3)) (TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451543 :: k3 ~> (k2 ~> k3)) = (Let6989586621680451545MfSym1 f6989586621680451543 :: TyFun k (TyFun k3 (TyFun (Maybe k2) (Maybe k3) -> Type) -> Type) -> Type) | |
type Apply (Let6989586621680451570MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451568 :: k2 ~> (k3 ~> k3)) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Let6989586621680451570MfSym0 :: TyFun (k2 ~> (k3 ~> k3)) (TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) -> Type) (f6989586621680451568 :: k2 ~> (k3 ~> k3)) = (Let6989586621680451570MfSym1 f6989586621680451568 :: TyFun k (TyFun (Maybe k2) (TyFun k3 (Maybe k3) -> Type) -> Type) -> Type) | |
type Apply (Traverse_6989586621680754401Sym0 :: TyFun (a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (Maybe a6989586621680748240 ~> f6989586621680748239 (Maybe b6989586621680748241)) -> Type) (a6989586621680754399 :: a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) | |
Defined in Data.Singletons.Prelude.Traversable type Apply (Traverse_6989586621680754401Sym0 :: TyFun (a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (Maybe a6989586621680748240 ~> f6989586621680748239 (Maybe b6989586621680748241)) -> Type) (a6989586621680754399 :: a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) = Traverse_6989586621680754401Sym1 a6989586621680754399 | |
type Apply (LiftA2_6989586621679607857Sym0 :: TyFun (a6989586621679544679 ~> (b6989586621679544680 ~> c6989586621679544681)) (Maybe a6989586621679544679 ~> (Maybe b6989586621679544680 ~> Maybe c6989586621679544681)) -> Type) (a6989586621679607854 :: a6989586621679544679 ~> (b6989586621679544680 ~> c6989586621679544681)) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (LiftA2_6989586621679607857Sym0 :: TyFun (a6989586621679544679 ~> (b6989586621679544680 ~> c6989586621679544681)) (Maybe a6989586621679544679 ~> (Maybe b6989586621679544680 ~> Maybe c6989586621679544681)) -> Type) (a6989586621679607854 :: a6989586621679544679 ~> (b6989586621679544680 ~> c6989586621679544681)) = LiftA2_6989586621679607857Sym1 a6989586621679607854 | |
type Apply (Maybe_Sym1 a6989586621679493735 a6989586621679493718 :: TyFun (a6989586621679493718 ~> b6989586621679493717) (Maybe a6989586621679493718 ~> b6989586621679493717) -> Type) (a6989586621679493736 :: a6989586621679493718 ~> b6989586621679493717) | |
Defined in Data.Singletons.Prelude.Maybe type Apply (Maybe_Sym1 a6989586621679493735 a6989586621679493718 :: TyFun (a6989586621679493718 ~> b6989586621679493717) (Maybe a6989586621679493718 ~> b6989586621679493717) -> Type) (a6989586621679493736 :: a6989586621679493718 ~> b6989586621679493717) = Maybe_Sym2 a6989586621679493735 a6989586621679493736 | |
type Apply (Lambda_6989586621680338811Sym1 a6989586621680338809 :: TyFun (k1 ~> First a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338810 :: k1 ~> First a) | |
type Apply (Lambda_6989586621680338899Sym1 a6989586621680338897 :: TyFun (k1 ~> Last a) (TyFun k1 (Maybe a) -> Type) -> Type) (k6989586621680338898 :: k1 ~> Last a) | |
Instances
Bounded Ordering | Since: base-2.1 |
Enum Ordering | Since: base-2.1 |
Eq Ordering | |
Data Ordering | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ordering -> c Ordering # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ordering # toConstr :: Ordering -> Constr # dataTypeOf :: Ordering -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Ordering) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ordering) # gmapT :: (forall b. Data b => b -> b) -> Ordering -> Ordering # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ordering -> r # gmapQ :: (forall d. Data d => d -> u) -> Ordering -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Ordering -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ordering -> m Ordering # | |
Ord Ordering | |
Defined in GHC.Classes | |
Read Ordering | Since: base-2.1 |
Show Ordering | Since: base-2.1 |
Ix Ordering | Since: base-2.1 |
Defined in GHC.Arr | |
Generic Ordering | |
Semigroup Ordering | Since: base-4.9.0.0 |
Monoid Ordering | Since: base-2.1 |
NFData Ordering | |
Defined in Control.DeepSeq | |
Hashable Ordering | |
Defined in Data.Hashable.Class | |
ToJSON Ordering | |
Defined in Data.Aeson.Types.ToJSON | |
FromJSON Ordering | |
Default Ordering | |
Defined in Data.Default.Class | |
PMonoid Ordering | |
SMonoid Ordering | |
Defined in Data.Singletons.Prelude.Monoid | |
PShow Ordering | |
SShow Ordering | |
PSemigroup Ordering | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
SSemigroup Ordering | |
PEnum Ordering | |
Defined in Data.Singletons.Prelude.Enum | |
SEnum Ordering | |
Defined in Data.Singletons.Prelude.Enum Methods sSucc :: Sing t -> Sing (Apply SuccSym0 t) # sPred :: Sing t -> Sing (Apply PredSym0 t) # sToEnum :: Sing t -> Sing (Apply ToEnumSym0 t) # sFromEnum :: Sing t -> Sing (Apply FromEnumSym0 t) # sEnumFromTo :: Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) # sEnumFromThenTo :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) # | |
PBounded Ordering | |
Defined in Data.Singletons.Prelude.Enum | |
SBounded Ordering | |
Defined in Data.Singletons.Prelude.Enum | |
POrd Ordering | |
SOrd Ordering | |
Defined in Data.Singletons.Prelude.Ord Methods sCompare :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) # (%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) # (%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) # (%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) # (%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) # sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) # sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) # | |
SEq Ordering | |
PEq Ordering | |
() :=> (Bounded Ordering) | |
() :=> (Enum Ordering) | |
() :=> (Read Ordering) | |
() :=> (Show Ordering) | |
() :=> (Semigroup Ordering) | |
() :=> (Monoid Ordering) | |
SuppressUnusedWarnings Compare_6989586621679391374Sym0 | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings FromEnum_6989586621679763788Sym0 | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ThenCmpSym0 | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Compare_6989586621679391384Sym0 | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ToEnum_6989586621679763782Sym0 | |
Defined in Data.Singletons.Prelude.Enum Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings ShowsPrec_6989586621680280994Sym0 | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Compare_6989586621679391394Sym0 | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Compare_6989586621679390986Sym0 | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Compare_6989586621679829801Sym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings Compare_6989586621679829819Sym0 | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SingI ThenCmpSym0 | |
Defined in Data.Singletons.Prelude.Ord Methods sing :: Sing ThenCmpSym0 # | |
SuppressUnusedWarnings (Compare_6989586621679391374Sym1 a6989586621679391372 :: TyFun Bool Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390897Sym0 :: TyFun [a3530822107858468865] ([a3530822107858468865] ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390863Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ThenCmpSym1 a6989586621679390477 :: TyFun Ordering Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391384Sym1 a6989586621679391382 :: TyFun Ordering Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680280994Sym1 a6989586621680280991 :: TyFun Ordering (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391394Sym1 a6989586621679391392 :: TyFun () Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380178Scrutinee_6989586621679380005Sym0 :: TyFun k1 (TyFun k1 Ordering -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380160Scrutinee_6989586621679380003Sym0 :: TyFun k1 (TyFun k1 Ordering -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380142Scrutinee_6989586621679380001Sym0 :: TyFun k1 (TyFun k1 Ordering -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380124Scrutinee_6989586621679379999Sym0 :: TyFun k1 (TyFun k1 Ordering -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679380114Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (CompareSym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390986Sym1 a6989586621679390984 :: TyFun Void Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829882Sym0 :: TyFun (Min a6989586621679050988) (Min a6989586621679050988 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829903Sym0 :: TyFun (Max a6989586621679050994) (Max a6989586621679050994 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829924Sym0 :: TyFun (First a6989586621679051008) (First a6989586621679051008 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829945Sym0 :: TyFun (Last a6989586621679051014) (Last a6989586621679051014 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829966Sym0 :: TyFun (WrappedMonoid m6989586621679051020) (WrappedMonoid m6989586621679051020 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829762Sym0 :: TyFun (Option a6989586621679051026) (Option a6989586621679051026 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391362Sym0 :: TyFun (Identity a6989586621679072641) (Identity a6989586621679072641 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621680334358Sym0 :: TyFun (First a6989586621679072651) (First a6989586621679072651 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621680334379Sym0 :: TyFun (Last a6989586621679072646) (Last a6989586621679072646 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829783Sym0 :: TyFun (Dual a6989586621679072622) (Dual a6989586621679072622 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829801Sym1 a6989586621679829799 :: TyFun All Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829819Sym1 a6989586621679829817 :: TyFun Any Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829840Sym0 :: TyFun (Sum a6989586621679072607) (Sum a6989586621679072607 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829861Sym0 :: TyFun (Product a6989586621679072612) (Product a6989586621679072612 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679389672Sym0 :: TyFun (Down a6989586621679389644) (Down a6989586621679389644 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390972Sym0 :: TyFun (NonEmpty a6989586621679055418) (NonEmpty a6989586621679055418 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ListsortBySym0 :: TyFun (a6989586621680387275 ~> (a6989586621680387275 ~> Ordering)) ([a6989586621680387275] ~> [a6989586621680387275]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal.Disambiguation Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (SortBySym0 :: TyFun (a6989586621679939707 ~> (a6989586621679939707 ~> Ordering)) ([a6989586621679939707] ~> [a6989586621679939707]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a6989586621679939704 ~> (a6989586621679939704 ~> Ordering)) ([a6989586621679939704] ~> a6989586621679939704) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a6989586621679939705 ~> (a6989586621679939705 ~> Ordering)) ([a6989586621679939705] ~> a6989586621679939705) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (InsertBySym0 :: TyFun (a6989586621679939706 ~> (a6989586621679939706 ~> Ordering)) (a6989586621679939706 ~> ([a6989586621679939706] ~> [a6989586621679939706])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SingI d => SingI (ThenCmpSym1 d :: TyFun Ordering Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods sing :: Sing (ThenCmpSym1 d) # | |
SOrd a => SingI (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods sing :: Sing CompareSym0 # | |
SingI (ListsortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) | |
SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing SortBySym0 # | |
SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> a) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> a) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal | |
SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods sing :: Sing InsertBySym0 # | |
SuppressUnusedWarnings (Compare_6989586621679390897Sym1 a6989586621679390895 :: TyFun [a3530822107858468865] Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390863Sym1 a6989586621679390861 :: TyFun (Maybe a3530822107858468865) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390943Sym0 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Either a6989586621679074205 b6989586621679074206 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391014Sym0 :: TyFun (a3530822107858468865, b3530822107858468866) ((a3530822107858468865, b3530822107858468866) ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380178Scrutinee_6989586621679380005Sym1 x6989586621679380176 :: TyFun k1 Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380160Scrutinee_6989586621679380003Sym1 x6989586621679380158 :: TyFun k1 Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380142Scrutinee_6989586621679380001Sym1 x6989586621679380140 :: TyFun k1 Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679380124Scrutinee_6989586621679379999Sym1 x6989586621679380122 :: TyFun k1 Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679380114Sym1 a6989586621679380112 :: TyFun a6989586621679379977 Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (CompareSym1 arg6989586621679380066 :: TyFun a6989586621679379977 Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829882Sym1 a6989586621679829880 :: TyFun (Min a6989586621679050988) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829903Sym1 a6989586621679829901 :: TyFun (Max a6989586621679050994) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621680882915Sym0 :: TyFun (Arg a6989586621680881641 b6989586621680881642) (Arg a6989586621680881641 b6989586621680881642 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829924Sym1 a6989586621679829922 :: TyFun (First a6989586621679051008) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829945Sym1 a6989586621679829943 :: TyFun (Last a6989586621679051014) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829966Sym1 a6989586621679829964 :: TyFun (WrappedMonoid m6989586621679051020) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829762Sym1 a6989586621679829760 :: TyFun (Option a6989586621679051026) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391362Sym1 a6989586621679391360 :: TyFun (Identity a6989586621679072641) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621680334358Sym1 a6989586621680334356 :: TyFun (First a6989586621679072651) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621680334379Sym1 a6989586621680334377 :: TyFun (Last a6989586621679072646) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Monoid Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829783Sym1 a6989586621679829781 :: TyFun (Dual a6989586621679072622) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829840Sym1 a6989586621679829838 :: TyFun (Sum a6989586621679072607) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679829861Sym1 a6989586621679829859 :: TyFun (Product a6989586621679072612) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679389672Sym1 a6989586621679389670 :: TyFun (Down a6989586621679389644) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390972Sym1 a6989586621679390970 :: TyFun (NonEmpty a6989586621679055418) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a6989586621680450640 ~> (a6989586621680450640 ~> Ordering)) (t6989586621680450639 a6989586621680450640 ~> a6989586621680450640) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a6989586621680450642 ~> (a6989586621680450642 ~> Ordering)) (t6989586621680450641 a6989586621680450642 ~> a6989586621680450642) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451161Max'Sym0 :: TyFun (k2 ~> (k2 ~> Ordering)) (TyFun k1 (TyFun k2 (TyFun k2 k2 -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621680451136Min'Sym0 :: TyFun (k2 ~> (k2 ~> Ordering)) (TyFun k1 (TyFun k2 (TyFun k2 k2 -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ComparingSym0 :: TyFun (b6989586621679379967 ~> a6989586621679379966) (b6989586621679379967 ~> (b6989586621679379967 ~> Ordering)) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
(SOrd a, SingI d) => SingI (CompareSym1 d :: TyFun a Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods sing :: Sing (CompareSym1 d) # | |
SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MinimumBySym0 # | |
SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) | |
Defined in Data.Singletons.Prelude.Foldable Methods sing :: Sing MaximumBySym0 # | |
SOrd a => SingI (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods sing :: Sing ComparingSym0 # | |
SuppressUnusedWarnings (Compare_6989586621679390943Sym1 a6989586621679390941 :: TyFun (Either a6989586621679074205 b6989586621679074206) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391014Sym1 a6989586621679391012 :: TyFun (a3530822107858468865, b3530822107858468866) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391055Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) ((a3530822107858468865, b3530822107858468866, c3530822107858468867) ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ComparingSym1 a6989586621679380057 :: TyFun b6989586621679379967 (b6989586621679379967 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621680882915Sym1 a6989586621680882913 :: TyFun (Arg a6989586621680881641 b6989586621680881642) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621680711406Sym0 :: TyFun (Const a6989586621680710909 b6989586621680710910) (Const a6989586621680710909 b6989586621680710910 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Const Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679950045MinBySym0 :: TyFun (k3 ~> (k3 ~> Ordering)) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k3 k3 -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679950015MaxBySym0 :: TyFun (k3 ~> (k3 ~> Ordering)) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k3 k3 -> Type) -> Type) -> Type) -> Type) -> Type) | |
Defined in Data.Singletons.Prelude.List.Internal Methods suppressUnusedWarnings :: () # | |
(SOrd a, SingI d) => SingI (ComparingSym1 d :: TyFun b (b ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods sing :: Sing (ComparingSym1 d) # | |
SuppressUnusedWarnings (Compare_6989586621679391055Sym1 a6989586621679391053 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391107Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ComparingSym2 a6989586621679380058 a6989586621679380057 :: TyFun b6989586621679379967 Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621680711406Sym1 a6989586621680711404 :: TyFun (Const a6989586621680710909 b6989586621680710910) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Const Methods suppressUnusedWarnings :: () # | |
(SOrd a, SingI d1, SingI d2) => SingI (ComparingSym2 d1 d2 :: TyFun b Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods sing :: Sing (ComparingSym2 d1 d2) # | |
SuppressUnusedWarnings (Compare_6989586621679391107Sym1 a6989586621679391105 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391170Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391170Sym1 a6989586621679391168 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391244Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391244Sym1 a6989586621679391242 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391329Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679391329Sym1 a6989586621679391327 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
type Rep Ordering | Since: base-4.6.0.0 |
type Mempty | |
Defined in Data.Singletons.Prelude.Monoid | |
type MaxBound | |
Defined in Data.Singletons.Prelude.Enum type MaxBound = MaxBound_6989586621679735900Sym0 | |
type MinBound | |
Defined in Data.Singletons.Prelude.Enum type MinBound = MinBound_6989586621679735898Sym0 | |
data Sing (a :: Ordering) | |
type Demote Ordering | |
Defined in Data.Singletons.Prelude.Instances | |
type Mconcat (arg :: [Ordering]) | |
type Show_ (arg :: Ordering) | |
type Sconcat (arg :: NonEmpty Ordering) | |
type FromEnum (a :: Ordering) | |
Defined in Data.Singletons.Prelude.Enum | |
type ToEnum a | |
Defined in Data.Singletons.Prelude.Enum | |
type Pred (arg :: Ordering) | |
type Succ (arg :: Ordering) | |
type Mappend (arg1 :: Ordering) (arg2 :: Ordering) | |
type ShowList (arg1 :: [Ordering]) arg2 | |
type (a1 :: Ordering) <> (a2 :: Ordering) | |
type EnumFromTo (arg1 :: Ordering) (arg2 :: Ordering) | |
type Min (arg1 :: Ordering) (arg2 :: Ordering) | |
type Max (arg1 :: Ordering) (arg2 :: Ordering) | |
type (arg1 :: Ordering) >= (arg2 :: Ordering) | |
type (arg1 :: Ordering) > (arg2 :: Ordering) | |
type (arg1 :: Ordering) <= (arg2 :: Ordering) | |
type (arg1 :: Ordering) < (arg2 :: Ordering) | |
type Compare (a1 :: Ordering) (a2 :: Ordering) | |
type (x :: Ordering) /= (y :: Ordering) | |
type (a :: Ordering) == (b :: Ordering) | |
Defined in Data.Singletons.Prelude.Eq | |
type ShowsPrec a1 (a2 :: Ordering) a3 | |
type EnumFromThenTo (arg1 :: Ordering) (arg2 :: Ordering) (arg3 :: Ordering) | |
type Apply ToEnum_6989586621679763782Sym0 (a6989586621679763781 :: Nat) | |
Defined in Data.Singletons.Prelude.Enum | |
type Apply FromEnum_6989586621679763788Sym0 (a6989586621679763787 :: Ordering) | |
Defined in Data.Singletons.Prelude.Enum | |
type Apply (Compare_6989586621679391374Sym1 a6989586621679391372 :: TyFun Bool Ordering -> Type) (a6989586621679391373 :: Bool) | |
type Apply (ThenCmpSym1 a6989586621679390477 :: TyFun Ordering Ordering -> Type) (a6989586621679390478 :: Ordering) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621679391384Sym1 a6989586621679391382 :: TyFun Ordering Ordering -> Type) (a6989586621679391383 :: Ordering) | |
type Apply (Compare_6989586621679391394Sym1 a6989586621679391392 :: TyFun () Ordering -> Type) (a6989586621679391393 :: ()) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621679390986Sym1 a6989586621679390984 :: TyFun Void Ordering -> Type) (a6989586621679390985 :: Void) | |
type Apply (Compare_6989586621679829801Sym1 a6989586621679829799 :: TyFun All Ordering -> Type) (a6989586621679829800 :: All) | |
type Apply (Compare_6989586621679829819Sym1 a6989586621679829817 :: TyFun Any Ordering -> Type) (a6989586621679829818 :: Any) | |
type Apply (Compare_6989586621679380114Sym1 a6989586621679380112 :: TyFun a Ordering -> Type) (a6989586621679380113 :: a) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (CompareSym1 arg6989586621679380066 :: TyFun a Ordering -> Type) (arg6989586621679380067 :: a) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Let6989586621679380178Scrutinee_6989586621679380005Sym1 x6989586621679380176 :: TyFun k1 Ordering -> Type) (y6989586621679380177 :: k1) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Let6989586621679380160Scrutinee_6989586621679380003Sym1 x6989586621679380158 :: TyFun k1 Ordering -> Type) (y6989586621679380159 :: k1) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Let6989586621679380142Scrutinee_6989586621679380001Sym1 x6989586621679380140 :: TyFun k1 Ordering -> Type) (y6989586621679380141 :: k1) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Let6989586621679380124Scrutinee_6989586621679379999Sym1 x6989586621679380122 :: TyFun k1 Ordering -> Type) (y6989586621679380123 :: k1) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (ComparingSym2 a6989586621679380058 a6989586621679380057 :: TyFun b Ordering -> Type) (a6989586621679380059 :: b) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621679390897Sym1 a6989586621679390895 :: TyFun [a] Ordering -> Type) (a6989586621679390896 :: [a]) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621679390863Sym1 a6989586621679390861 :: TyFun (Maybe a) Ordering -> Type) (a6989586621679390862 :: Maybe a) | |
type Apply (Compare_6989586621679829882Sym1 a6989586621679829880 :: TyFun (Min a) Ordering -> Type) (a6989586621679829881 :: Min a) | |
type Apply (Compare_6989586621679829903Sym1 a6989586621679829901 :: TyFun (Max a) Ordering -> Type) (a6989586621679829902 :: Max a) | |
type Apply (Compare_6989586621679829924Sym1 a6989586621679829922 :: TyFun (First a) Ordering -> Type) (a6989586621679829923 :: First a) | |
type Apply (Compare_6989586621679829945Sym1 a6989586621679829943 :: TyFun (Last a) Ordering -> Type) (a6989586621679829944 :: Last a) | |
type Apply (Compare_6989586621679829966Sym1 a6989586621679829964 :: TyFun (WrappedMonoid m) Ordering -> Type) (a6989586621679829965 :: WrappedMonoid m) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (Compare_6989586621679829966Sym1 a6989586621679829964 :: TyFun (WrappedMonoid m) Ordering -> Type) (a6989586621679829965 :: WrappedMonoid m) = Compare_6989586621679829966 a6989586621679829964 a6989586621679829965 | |
type Apply (Compare_6989586621679829762Sym1 a6989586621679829760 :: TyFun (Option a) Ordering -> Type) (a6989586621679829761 :: Option a) | |
type Apply (Compare_6989586621679391362Sym1 a6989586621679391360 :: TyFun (Identity a) Ordering -> Type) (a6989586621679391361 :: Identity a) | |
type Apply (Compare_6989586621680334358Sym1 a6989586621680334356 :: TyFun (First a) Ordering -> Type) (a6989586621680334357 :: First a) | |
type Apply (Compare_6989586621680334379Sym1 a6989586621680334377 :: TyFun (Last a) Ordering -> Type) (a6989586621680334378 :: Last a) | |
type Apply (Compare_6989586621679829783Sym1 a6989586621679829781 :: TyFun (Dual a) Ordering -> Type) (a6989586621679829782 :: Dual a) | |
type Apply (Compare_6989586621679829840Sym1 a6989586621679829838 :: TyFun (Sum a) Ordering -> Type) (a6989586621679829839 :: Sum a) | |
type Apply (Compare_6989586621679829861Sym1 a6989586621679829859 :: TyFun (Product a) Ordering -> Type) (a6989586621679829860 :: Product a) | |
type Apply (Compare_6989586621679389672Sym1 a6989586621679389670 :: TyFun (Down a) Ordering -> Type) (a6989586621679389671 :: Down a) | |
type Apply (Compare_6989586621679390972Sym1 a6989586621679390970 :: TyFun (NonEmpty a) Ordering -> Type) (a6989586621679390971 :: NonEmpty a) | |
type Apply (Compare_6989586621679390943Sym1 a6989586621679390941 :: TyFun (Either a b) Ordering -> Type) (a6989586621679390942 :: Either a b) | |
type Apply (Compare_6989586621679391014Sym1 a6989586621679391012 :: TyFun (a, b) Ordering -> Type) (a6989586621679391013 :: (a, b)) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621680882915Sym1 a6989586621680882913 :: TyFun (Arg a b) Ordering -> Type) (a6989586621680882914 :: Arg a b) | |
type Apply (Compare_6989586621679391055Sym1 a6989586621679391053 :: TyFun (a, b, c) Ordering -> Type) (a6989586621679391054 :: (a, b, c)) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621680711406Sym1 a6989586621680711404 :: TyFun (Const a b) Ordering -> Type) (a6989586621680711405 :: Const a b) | |
type Apply (Compare_6989586621679391107Sym1 a6989586621679391105 :: TyFun (a, b, c, d) Ordering -> Type) (a6989586621679391106 :: (a, b, c, d)) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621679391170Sym1 a6989586621679391168 :: TyFun (a, b, c, d, e) Ordering -> Type) (a6989586621679391169 :: (a, b, c, d, e)) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621679391244Sym1 a6989586621679391242 :: TyFun (a, b, c, d, e, f) Ordering -> Type) (a6989586621679391243 :: (a, b, c, d, e, f)) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (Compare_6989586621679391329Sym1 a6989586621679391327 :: TyFun (a, b, c, d, e, f, g) Ordering -> Type) (a6989586621679391328 :: (a, b, c, d, e, f, g)) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply Compare_6989586621679391374Sym0 (a6989586621679391372 :: Bool) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply ThenCmpSym0 (a6989586621679390477 :: Ordering) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply Compare_6989586621679391384Sym0 (a6989586621679391382 :: Ordering) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply ShowsPrec_6989586621680280994Sym0 (a6989586621680280991 :: Nat) | |
Defined in Data.Singletons.Prelude.Show | |
type Apply Compare_6989586621679391394Sym0 (a6989586621679391392 :: ()) | |
Defined in Data.Singletons.Prelude.Ord type Apply Compare_6989586621679391394Sym0 (a6989586621679391392 :: ()) = Compare_6989586621679391394Sym1 a6989586621679391392 | |
type Apply Compare_6989586621679390986Sym0 (a6989586621679390984 :: Void) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply Compare_6989586621679829801Sym0 (a6989586621679829799 :: All) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply Compare_6989586621679829819Sym0 (a6989586621679829817 :: Any) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply (Let6989586621679380178Scrutinee_6989586621679380005Sym0 :: TyFun k1 (TyFun k1 Ordering -> Type) -> Type) (x6989586621679380176 :: k1) | |
type Apply (Let6989586621679380160Scrutinee_6989586621679380003Sym0 :: TyFun k1 (TyFun k1 Ordering -> Type) -> Type) (x6989586621679380158 :: k1) | |
type Apply (Let6989586621679380142Scrutinee_6989586621679380001Sym0 :: TyFun k1 (TyFun k1 Ordering -> Type) -> Type) (x6989586621679380140 :: k1) | |
type Apply (Let6989586621679380124Scrutinee_6989586621679379999Sym0 :: TyFun k1 (TyFun k1 Ordering -> Type) -> Type) (x6989586621679380122 :: k1) | |
type Apply (ShowsPrec_6989586621680280994Sym1 a6989586621680280991 :: TyFun Ordering (Symbol ~> Symbol) -> Type) (a6989586621680280992 :: Ordering) | |
type Apply (Compare_6989586621679380114Sym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Ordering) -> Type) (a6989586621679380112 :: a6989586621679379977) | |
type Apply (CompareSym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Ordering) -> Type) (arg6989586621679380066 :: a6989586621679379977) | |
Defined in Data.Singletons.Prelude.Ord type Apply (CompareSym0 :: TyFun a6989586621679379977 (a6989586621679379977 ~> Ordering) -> Type) (arg6989586621679380066 :: a6989586621679379977) = CompareSym1 arg6989586621679380066 | |
type Apply (ComparingSym1 a6989586621679380057 :: TyFun b6989586621679379967 (b6989586621679379967 ~> Ordering) -> Type) (a6989586621679380058 :: b6989586621679379967) | |
Defined in Data.Singletons.Prelude.Ord type Apply (ComparingSym1 a6989586621679380057 :: TyFun b6989586621679379967 (b6989586621679379967 ~> Ordering) -> Type) (a6989586621679380058 :: b6989586621679379967) = ComparingSym2 a6989586621679380057 a6989586621679380058 | |
type Apply (Compare_6989586621679390897Sym0 :: TyFun [a3530822107858468865] ([a3530822107858468865] ~> Ordering) -> Type) (a6989586621679390895 :: [a3530822107858468865]) | |
type Apply (Compare_6989586621679390863Sym0 :: TyFun (Maybe a3530822107858468865) (Maybe a3530822107858468865 ~> Ordering) -> Type) (a6989586621679390861 :: Maybe a3530822107858468865) | |
type Apply (Compare_6989586621679829882Sym0 :: TyFun (Min a6989586621679050988) (Min a6989586621679050988 ~> Ordering) -> Type) (a6989586621679829880 :: Min a6989586621679050988) | |
type Apply (Compare_6989586621679829903Sym0 :: TyFun (Max a6989586621679050994) (Max a6989586621679050994 ~> Ordering) -> Type) (a6989586621679829901 :: Max a6989586621679050994) | |
type Apply (Compare_6989586621679829924Sym0 :: TyFun (First a6989586621679051008) (First a6989586621679051008 ~> Ordering) -> Type) (a6989586621679829922 :: First a6989586621679051008) | |
type Apply (Compare_6989586621679829945Sym0 :: TyFun (Last a6989586621679051014) (Last a6989586621679051014 ~> Ordering) -> Type) (a6989586621679829943 :: Last a6989586621679051014) | |
type Apply (Compare_6989586621679829966Sym0 :: TyFun (WrappedMonoid m6989586621679051020) (WrappedMonoid m6989586621679051020 ~> Ordering) -> Type) (a6989586621679829964 :: WrappedMonoid m6989586621679051020) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal type Apply (Compare_6989586621679829966Sym0 :: TyFun (WrappedMonoid m6989586621679051020) (WrappedMonoid m6989586621679051020 ~> Ordering) -> Type) (a6989586621679829964 :: WrappedMonoid m6989586621679051020) = Compare_6989586621679829966Sym1 a6989586621679829964 | |
type Apply (Compare_6989586621679829762Sym0 :: TyFun (Option a6989586621679051026) (Option a6989586621679051026 ~> Ordering) -> Type) (a6989586621679829760 :: Option a6989586621679051026) | |
type Apply (Compare_6989586621679391362Sym0 :: TyFun (Identity a6989586621679072641) (Identity a6989586621679072641 ~> Ordering) -> Type) (a6989586621679391360 :: Identity a6989586621679072641) | |
type Apply (Compare_6989586621680334358Sym0 :: TyFun (First a6989586621679072651) (First a6989586621679072651 ~> Ordering) -> Type) (a6989586621680334356 :: First a6989586621679072651) | |
type Apply (Compare_6989586621680334379Sym0 :: TyFun (Last a6989586621679072646) (Last a6989586621679072646 ~> Ordering) -> Type) (a6989586621680334377 :: Last a6989586621679072646) | |
type Apply (Compare_6989586621679829783Sym0 :: TyFun (Dual a6989586621679072622) (Dual a6989586621679072622 ~> Ordering) -> Type) (a6989586621679829781 :: Dual a6989586621679072622) | |
type Apply (Compare_6989586621679829840Sym0 :: TyFun (Sum a6989586621679072607) (Sum a6989586621679072607 ~> Ordering) -> Type) (a6989586621679829838 :: Sum a6989586621679072607) | |
type Apply (Compare_6989586621679829861Sym0 :: TyFun (Product a6989586621679072612) (Product a6989586621679072612 ~> Ordering) -> Type) (a6989586621679829859 :: Product a6989586621679072612) | |
type Apply (Compare_6989586621679389672Sym0 :: TyFun (Down a6989586621679389644) (Down a6989586621679389644 ~> Ordering) -> Type) (a6989586621679389670 :: Down a6989586621679389644) | |
type Apply (Compare_6989586621679390972Sym0 :: TyFun (NonEmpty a6989586621679055418) (NonEmpty a6989586621679055418 ~> Ordering) -> Type) (a6989586621679390970 :: NonEmpty a6989586621679055418) | |
type Apply (ListsortBySym0 :: TyFun (a6989586621680387275 ~> (a6989586621680387275 ~> Ordering)) ([a6989586621680387275] ~> [a6989586621680387275]) -> Type) (a6989586621680388336 :: a6989586621680387275 ~> (a6989586621680387275 ~> Ordering)) | |
type Apply (SortBySym0 :: TyFun (a6989586621679939707 ~> (a6989586621679939707 ~> Ordering)) ([a6989586621679939707] ~> [a6989586621679939707]) -> Type) (a6989586621679949297 :: a6989586621679939707 ~> (a6989586621679939707 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (MaximumBySym0 :: TyFun (a6989586621679939705 ~> (a6989586621679939705 ~> Ordering)) ([a6989586621679939705] ~> a6989586621679939705) -> Type) (a6989586621679950004 :: a6989586621679939705 ~> (a6989586621679939705 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (MinimumBySym0 :: TyFun (a6989586621679939704 ~> (a6989586621679939704 ~> Ordering)) ([a6989586621679939704] ~> a6989586621679939704) -> Type) (a6989586621679950034 :: a6989586621679939704 ~> (a6989586621679939704 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.List.Internal | |
type Apply (InsertBySym0 :: TyFun (a6989586621679939706 ~> (a6989586621679939706 ~> Ordering)) (a6989586621679939706 ~> ([a6989586621679939706] ~> [a6989586621679939706])) -> Type) (a6989586621679949267 :: a6989586621679939706 ~> (a6989586621679939706 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (InsertBySym0 :: TyFun (a6989586621679939706 ~> (a6989586621679939706 ~> Ordering)) (a6989586621679939706 ~> ([a6989586621679939706] ~> [a6989586621679939706])) -> Type) (a6989586621679949267 :: a6989586621679939706 ~> (a6989586621679939706 ~> Ordering)) = InsertBySym1 a6989586621679949267 | |
type Apply (Let6989586621680451136Min'Sym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (cmp6989586621680451134 :: k1 ~> (k1 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Let6989586621680451136Min'Sym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (cmp6989586621680451134 :: k1 ~> (k1 ~> Ordering)) = (Let6989586621680451136Min'Sym1 cmp6989586621680451134 :: TyFun k2 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) | |
type Apply (Let6989586621680451161Max'Sym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (cmp6989586621680451159 :: k1 ~> (k1 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (Let6989586621680451161Max'Sym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) (cmp6989586621680451159 :: k1 ~> (k1 ~> Ordering)) = (Let6989586621680451161Max'Sym1 cmp6989586621680451159 :: TyFun k2 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) | |
type Apply (Compare_6989586621679390943Sym0 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Either a6989586621679074205 b6989586621679074206 ~> Ordering) -> Type) (a6989586621679390941 :: Either a6989586621679074205 b6989586621679074206) | |
Defined in Data.Singletons.Prelude.Ord type Apply (Compare_6989586621679390943Sym0 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Either a6989586621679074205 b6989586621679074206 ~> Ordering) -> Type) (a6989586621679390941 :: Either a6989586621679074205 b6989586621679074206) = Compare_6989586621679390943Sym1 a6989586621679390941 | |
type Apply (Compare_6989586621679391014Sym0 :: TyFun (a3530822107858468865, b3530822107858468866) ((a3530822107858468865, b3530822107858468866) ~> Ordering) -> Type) (a6989586621679391012 :: (a3530822107858468865, b3530822107858468866)) | |
Defined in Data.Singletons.Prelude.Ord | |
type Apply (MaximumBySym0 :: TyFun (a6989586621680450642 ~> (a6989586621680450642 ~> Ordering)) (t6989586621680450641 a6989586621680450642 ~> a6989586621680450642) -> Type) (a6989586621680451153 :: a6989586621680450642 ~> (a6989586621680450642 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MaximumBySym0 :: TyFun (a6989586621680450642 ~> (a6989586621680450642 ~> Ordering)) (t6989586621680450641 a6989586621680450642 ~> a6989586621680450642) -> Type) (a6989586621680451153 :: a6989586621680450642 ~> (a6989586621680450642 ~> Ordering)) = (MaximumBySym1 a6989586621680451153 t6989586621680450641 :: TyFun (t6989586621680450641 a6989586621680450642) a6989586621680450642 -> Type) | |
type Apply (MinimumBySym0 :: TyFun (a6989586621680450640 ~> (a6989586621680450640 ~> Ordering)) (t6989586621680450639 a6989586621680450640 ~> a6989586621680450640) -> Type) (a6989586621680451128 :: a6989586621680450640 ~> (a6989586621680450640 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.Foldable type Apply (MinimumBySym0 :: TyFun (a6989586621680450640 ~> (a6989586621680450640 ~> Ordering)) (t6989586621680450639 a6989586621680450640 ~> a6989586621680450640) -> Type) (a6989586621680451128 :: a6989586621680450640 ~> (a6989586621680450640 ~> Ordering)) = (MinimumBySym1 a6989586621680451128 t6989586621680450639 :: TyFun (t6989586621680450639 a6989586621680450640) a6989586621680450640 -> Type) | |
type Apply (ComparingSym0 :: TyFun (b6989586621679379967 ~> a6989586621679379966) (b6989586621679379967 ~> (b6989586621679379967 ~> Ordering)) -> Type) (a6989586621679380057 :: b6989586621679379967 ~> a6989586621679379966) | |
Defined in Data.Singletons.Prelude.Ord type Apply (ComparingSym0 :: TyFun (b6989586621679379967 ~> a6989586621679379966) (b6989586621679379967 ~> (b6989586621679379967 ~> Ordering)) -> Type) (a6989586621679380057 :: b6989586621679379967 ~> a6989586621679379966) = ComparingSym1 a6989586621679380057 | |
type Apply (Compare_6989586621680882915Sym0 :: TyFun (Arg a6989586621680881641 b6989586621680881642) (Arg a6989586621680881641 b6989586621680881642 ~> Ordering) -> Type) (a6989586621680882913 :: Arg a6989586621680881641 b6989586621680881642) | |
Defined in Data.Singletons.Prelude.Semigroup | |
type Apply (Let6989586621679950015MaxBySym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k3 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) -> Type) (cmp6989586621679950008 :: k1 ~> (k1 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679950015MaxBySym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k3 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) -> Type) (cmp6989586621679950008 :: k1 ~> (k1 ~> Ordering)) = (Let6989586621679950015MaxBySym1 cmp6989586621679950008 :: TyFun k2 (TyFun k3 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) | |
type Apply (Let6989586621679950045MinBySym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k3 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) -> Type) (cmp6989586621679950038 :: k1 ~> (k1 ~> Ordering)) | |
Defined in Data.Singletons.Prelude.List.Internal type Apply (Let6989586621679950045MinBySym0 :: TyFun (k1 ~> (k1 ~> Ordering)) (TyFun k2 (TyFun k3 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) -> Type) (cmp6989586621679950038 :: k1 ~> (k1 ~> Ordering)) = (Let6989586621679950045MinBySym1 cmp6989586621679950038 :: TyFun k2 (TyFun k3 (TyFun k1 (TyFun k1 k1 -> Type) -> Type) -> Type) -> Type) | |
type Apply (Compare_6989586621679391055Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) ((a3530822107858468865, b3530822107858468866, c3530822107858468867) ~> Ordering) -> Type) (a6989586621679391053 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867)) | |
Defined in Data.Singletons.Prelude.Ord type Apply (Compare_6989586621679391055Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867) ((a3530822107858468865, b3530822107858468866, c3530822107858468867) ~> Ordering) -> Type) (a6989586621679391053 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867)) = Compare_6989586621679391055Sym1 a6989586621679391053 | |
type Apply (Compare_6989586621680711406Sym0 :: TyFun (Const a6989586621680710909 b6989586621680710910) (Const a6989586621680710909 b6989586621680710910 ~> Ordering) -> Type) (a6989586621680711404 :: Const a6989586621680710909 b6989586621680710910) | |
Defined in Data.Singletons.Prelude.Const type Apply (Compare_6989586621680711406Sym0 :: TyFun (Const a6989586621680710909 b6989586621680710910) (Const a6989586621680710909 b6989586621680710910 ~> Ordering) -> Type) (a6989586621680711404 :: Const a6989586621680710909 b6989586621680710910) = Compare_6989586621680711406Sym1 a6989586621680711404 | |
type Apply (Compare_6989586621679391107Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) ~> Ordering) -> Type) (a6989586621679391105 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868)) | |
Defined in Data.Singletons.Prelude.Ord type Apply (Compare_6989586621679391107Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868) ~> Ordering) -> Type) (a6989586621679391105 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868)) = Compare_6989586621679391107Sym1 a6989586621679391105 | |
type Apply (Compare_6989586621679391170Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) ~> Ordering) -> Type) (a6989586621679391168 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869)) | |
Defined in Data.Singletons.Prelude.Ord type Apply (Compare_6989586621679391170Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869) ~> Ordering) -> Type) (a6989586621679391168 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869)) = Compare_6989586621679391170Sym1 a6989586621679391168 | |
type Apply (Compare_6989586621679391244Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) ~> Ordering) -> Type) (a6989586621679391242 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870)) | |
Defined in Data.Singletons.Prelude.Ord type Apply (Compare_6989586621679391244Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870) ~> Ordering) -> Type) (a6989586621679391242 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870)) = Compare_6989586621679391244Sym1 a6989586621679391242 | |
type Apply (Compare_6989586621679391329Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) ~> Ordering) -> Type) (a6989586621679391327 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871)) | |
Defined in Data.Singletons.Prelude.Ord type Apply (Compare_6989586621679391329Sym0 :: TyFun (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) ((a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871) ~> Ordering) -> Type) (a6989586621679391327 :: (a3530822107858468865, b3530822107858468866, c3530822107858468867, d3530822107858468868, e3530822107858468869, f3530822107858468870, g3530822107858468871)) = Compare_6989586621679391329Sym1 a6989586621679391327 |
A value of type
is a computation which, when performed,
does some I/O before returning a value of type IO
aa
.
There is really only one way to "perform" an I/O action: bind it to
Main.main
in your program. When your program is run, the I/O will
be performed. It isn't possible to perform I/O from an arbitrary
function, unless that function is itself in the IO
monad and called
at some point, directly or indirectly, from Main.main
.
IO
is a monad, so IO
actions can be combined using either the do-notation
or the >>
and >>=
operations from the Monad
class.
Instances
The Either
type represents values with two possibilities: a value of
type
is either Either
a b
or Left
a
.Right
b
The Either
type is sometimes used to represent a value which is
either correct or an error; by convention, the Left
constructor is
used to hold an error value and the Right
constructor is used to
hold a correct value (mnemonic: "right" also means "correct").
Examples
The type
is the type of values which can be either
a Either
String
Int
String
or an Int
. The Left
constructor can be used only on
String
s, and the Right
constructor can be used only on Int
s:
>>>
let s = Left "foo" :: Either String Int
>>>
s
Left "foo">>>
let n = Right 3 :: Either String Int
>>>
n
Right 3>>>
:type s
s :: Either String Int>>>
:type n
n :: Either String Int
The fmap
from our Functor
instance will ignore Left
values, but
will apply the supplied function to values contained in a Right
:
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
fmap (*2) s
Left "foo">>>
fmap (*2) n
Right 6
The Monad
instance for Either
allows us to chain together multiple
actions which may fail, and fail overall if any of the individual
steps failed. First we'll write a function that can either parse an
Int
from a Char
, or fail.
>>>
import Data.Char ( digitToInt, isDigit )
>>>
:{
let parseEither :: Char -> Either String Int parseEither c | isDigit c = Right (digitToInt c) | otherwise = Left "parse error">>>
:}
The following should work, since both '1'
and '2'
can be
parsed as Int
s.
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither '1' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Right 3
But the following should fail overall, since the first operation where
we attempt to parse 'm'
as an Int
will fail:
>>>
:{
let parseMultiple :: Either String Int parseMultiple = do x <- parseEither 'm' y <- parseEither '2' return (x + y)>>>
:}
>>>
parseMultiple
Left "parse error"
Instances
ToJSON2 Either | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Either a b -> Value # liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Either a b] -> Value # liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Either a b -> Encoding # liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Either a b] -> Encoding # | |
FromJSON2 Either | |
Defined in Data.Aeson.Types.FromJSON | |
Bitraversable Either | Since: base-4.10.0.0 |
Defined in Data.Bitraversable Methods bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Either a b -> f (Either c d) # | |
Bifoldable Either | Since: base-4.10.0.0 |
Bifunctor Either | Since: base-4.8.0.0 |
Eq2 Either | Since: base-4.9.0.0 |
Ord2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read2 Either | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (Either a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [Either a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (Either a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [Either a b] # | |
Show2 Either | Since: base-4.9.0.0 |
NFData2 Either | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable2 Either | |
Defined in Data.Hashable.Class | |
() :=> (Monad (Either a)) | |
() :=> (Functor (Either a)) | |
() :=> (Applicative (Either a)) | |
Defined in Data.Constraint Methods ins :: () :- Applicative (Either a) # | |
MonadError e (Either e) | |
Defined in Control.Monad.Error.Class | |
(CRTElt t r, Fact m) => C r (CycRepEC t m r) Source # | |
Defined in Crypto.Lol.Cyclotomic.CycRep | |
Monad (Either e) | Since: base-4.4.0.0 |
Functor (Either a) | Since: base-3.0 |
MonadFix (Either e) | Since: base-4.3.0.0 |
Defined in Control.Monad.Fix | |
Applicative (Either e) | Since: base-3.0 |
Foldable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Foldable Methods fold :: Monoid m => Either a m -> m # foldMap :: Monoid m => (a0 -> m) -> Either a a0 -> m # foldr :: (a0 -> b -> b) -> b -> Either a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> Either a a0 -> b # foldl :: (b -> a0 -> b) -> b -> Either a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> Either a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> Either a a0 -> a0 # toList :: Either a a0 -> [a0] # length :: Either a a0 -> Int # elem :: Eq a0 => a0 -> Either a a0 -> Bool # maximum :: Ord a0 => Either a a0 -> a0 # minimum :: Ord a0 => Either a a0 -> a0 # | |
Traversable (Either a) | Since: base-4.7.0.0 |
Defined in Data.Traversable | |
ToJSON a => ToJSON1 (Either a) | |
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON :: (a0 -> Value) -> ([a0] -> Value) -> Either a a0 -> Value # liftToJSONList :: (a0 -> Value) -> ([a0] -> Value) -> [Either a a0] -> Value # liftToEncoding :: (a0 -> Encoding) -> ([a0] -> Encoding) -> Either a a0 -> Encoding # liftToEncodingList :: (a0 -> Encoding) -> ([a0] -> Encoding) -> [Either a a0] -> Encoding # | |
FromJSON a => FromJSON1 (Either a) | |
Eq a => Eq1 (Either a) | Since: base-4.9.0.0 |
Ord a => Ord1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes | |
Read a => Read1 (Either a) | Since: base-4.9.0.0 |
Defined in Data.Functor.Classes Methods liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (Either a a0) # liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [Either a a0] # liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (Either a a0) # liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [Either a a0] # | |
Show a => Show1 (Either a) | Since: base-4.9.0.0 |
NFData a => NFData1 (Either a) | Since: deepseq-1.4.3.0 |
Defined in Control.DeepSeq | |
Hashable a => Hashable1 (Either a) | |
Defined in Data.Hashable.Class | |
PTraversable (Either a) | |
STraversable (Either a) | |
Defined in Data.Singletons.Prelude.Traversable Methods sTraverse :: SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply TraverseSym0 t1) t2) # sSequenceA :: SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 t1) # sMapM :: SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply MapMSym0 t1) t2) # sSequence :: SMonad m => Sing t1 -> Sing (Apply SequenceSym0 t1) # | |
PFoldable (Either a) | |
SFoldable (Either a) | |
Defined in Data.Singletons.Prelude.Foldable Methods sFold :: SMonoid m => Sing t1 -> Sing (Apply FoldSym0 t1) # sFoldMap :: SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 t1) t2) # sFoldr :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldrSym0 t1) t2) t3) # sFoldr' :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldr'Sym0 t1) t2) t3) # sFoldl :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply FoldlSym0 t1) t2) t3) # sFoldl' :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply Foldl'Sym0 t1) t2) t3) # sFoldr1 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) # sFoldl1 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) # sToList :: Sing t1 -> Sing (Apply ToListSym0 t1) # sNull :: Sing t1 -> Sing (Apply NullSym0 t1) # sLength :: Sing t1 -> Sing (Apply LengthSym0 t1) # sElem :: SEq a0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) # sMaximum :: SOrd a0 => Sing t1 -> Sing (Apply MaximumSym0 t1) # sMinimum :: SOrd a0 => Sing t1 -> Sing (Apply MinimumSym0 t1) # sSum :: SNum a0 => Sing t1 -> Sing (Apply SumSym0 t1) # sProduct :: SNum a0 => Sing t1 -> Sing (Apply ProductSym0 t1) # | |
PFunctor (Either a) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
PApplicative (Either e) | |
PMonad (Either e) | |
SFunctor (Either a) | |
SApplicative (Either e) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods sPure :: Sing t -> Sing (Apply PureSym0 t) # (%<*>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*>@#@$) t1) t2) # sLiftA2 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply LiftA2Sym0 t1) t2) t3) # (%*>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (*>@#@$) t1) t2) # (%<*) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<*@#@$) t1) t2) # | |
SMonad (Either e) | |
Generic1 (Either a :: Type -> Type) | |
(Eq a, Eq b) => Eq (Either a b) | Since: base-2.1 |
(Data a, Data b) => Data (Either a b) | Since: base-4.0.0.0 |
Defined in Data.Data Methods gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> Either a b -> c (Either a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Either a b) # toConstr :: Either a b -> Constr # dataTypeOf :: Either a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Either a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Either a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> Either a b -> Either a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Either a b -> r # gmapQ :: (forall d. Data d => d -> u) -> Either a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Either a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Either a b -> m (Either a b) # | |
(Ord a, Ord b) => Ord (Either a b) | Since: base-2.1 |
(Read a, Read b) => Read (Either a b) | Since: base-3.0 |
(Show a, Show b) => Show (Either a b) | Since: base-3.0 |
Generic (Either a b) | |
Semigroup (Either a b) | Since: base-4.9.0.0 |
(Lift a, Lift b) => Lift (Either a b) | |
(NFData a, NFData b) => NFData (Either a b) | |
Defined in Control.DeepSeq | |
(Hashable a, Hashable b) => Hashable (Either a b) | |
Defined in Data.Hashable.Class | |
(ToJSON a, ToJSON b) => ToJSON (Either a b) | |
Defined in Data.Aeson.Types.ToJSON | |
(FromJSON a, FromJSON b) => FromJSON (Either a b) | |
PShow (Either a b) | |
(SShow a, SShow b) => SShow (Either a b) | |
PSemigroup (Either a b) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
SSemigroup (Either a b) | |
POrd (Either a b) | |
(SOrd a, SOrd b) => SOrd (Either a b) | |
Defined in Data.Singletons.Prelude.Ord Methods sCompare :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) # (%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) # (%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) # (%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) # (%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) # sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) # sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) # | |
(SEq a, SEq b) => SEq (Either a b) | |
PEq (Either a b) | |
(Eq a, Eq b) :=> (Eq (Either a b)) | |
(Ord a, Ord b) :=> (Ord (Either a b)) | |
(Read a, Read b) :=> (Read (Either a b)) | |
(Show a, Show b) :=> (Show (Either a b)) | |
SuppressUnusedWarnings (RightsSym0 :: TyFun [Either a6989586621680432179 b6989586621680432180] [b6989586621680432180] -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (PartitionEithersSym0 :: TyFun [Either a6989586621680432177 b6989586621680432178] ([a6989586621680432177], [b6989586621680432178]) -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (LeftsSym0 :: TyFun [Either a6989586621680432181 b6989586621680432182] [a6989586621680432181] -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a6989586621680432173 b6989586621680432174) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a6989586621680432175 b6989586621680432176) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390943Sym0 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Either a6989586621679074205 b6989586621679074206 ~> Ordering) -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680280907Sym0 :: TyFun Nat (Either a6989586621679074205 b6989586621679074206 ~> (Symbol ~> Symbol)) -> Type) | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Pure_6989586621679607989Sym0 :: TyFun a6989586621679544676 (Either e6989586621679607257 a6989586621679544676) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (RightSym0 :: TyFun b6989586621679074206 (Either a6989586621679074205 b6989586621679074206) -> Type) | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (LeftSym0 :: TyFun a6989586621679074205 (Either a6989586621679074205 b6989586621679074206) -> Type) | |
Defined in Data.Singletons.Prelude.Instances Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Let6989586621679811171ASym0 :: TyFun k1 (Either a6989586621679074205 k1) -> Type) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal Methods suppressUnusedWarnings :: () # | |
SingI (RightsSym0 :: TyFun [Either a b] [b] -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods sing :: Sing RightsSym0 # | |
SingI (PartitionEithersSym0 :: TyFun [Either a b] ([a], [b]) -> Type) | |
Defined in Data.Singletons.Prelude.Either | |
SingI (LeftsSym0 :: TyFun [Either a b] [a] -> Type) | |
Defined in Data.Singletons.Prelude.Either | |
SingI (IsRightSym0 :: TyFun (Either a b) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods sing :: Sing IsRightSym0 # | |
SingI (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods sing :: Sing IsLeftSym0 # | |
SingI (RightSym0 :: TyFun b (Either a b) -> Type) | |
Defined in Data.Singletons.Prelude.Instances | |
SingI (LeftSym0 :: TyFun a (Either a b) -> Type) | |
Defined in Data.Singletons.Prelude.Instances | |
SuppressUnusedWarnings (TFHelper_6989586621679608113Sym0 :: TyFun (Either e6989586621679607274 a6989586621679544700) ((a6989586621679544700 ~> Either e6989586621679607274 b6989586621679544701) ~> Either e6989586621679607274 b6989586621679544701) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679608001Sym0 :: TyFun (Either e6989586621679607257 (a6989586621679544677 ~> b6989586621679544678)) (Either e6989586621679607257 a6989586621679544677 ~> Either e6989586621679607257 b6989586621679544678) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (ShowsPrec_6989586621680280907Sym1 a6989586621680280904 a6989586621679074205 b6989586621679074206 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Symbol ~> Symbol) -> Type) | |
Defined in Data.Singletons.Prelude.Show Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Compare_6989586621679390943Sym1 a6989586621679390941 :: TyFun (Either a6989586621679074205 b6989586621679074206) Ordering -> Type) | |
Defined in Data.Singletons.Prelude.Ord Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679607819Sym0 :: TyFun a6989586621679544673 (Either a6989586621679607245 b6989586621679544674 ~> Either a6989586621679607245 a6989586621679544673) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Fmap_6989586621679607791Sym0 :: TyFun (a6989586621679544671 ~> b6989586621679544672) (Either a6989586621679607245 a6989586621679544671 ~> Either a6989586621679607245 b6989586621679544672) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Either_Sym0 :: TyFun (a6989586621680430703 ~> c6989586621680430704) ((b6989586621680430705 ~> c6989586621680430704) ~> (Either a6989586621680430703 b6989586621680430705 ~> c6989586621680430704)) -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SingI (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods sing :: Sing Either_Sym0 # | |
SuppressUnusedWarnings (TFHelper_6989586621679608001Sym1 a6989586621679607999 :: TyFun (Either e6989586621679607257 a6989586621679544677) (Either e6989586621679607257 b6989586621679544678) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679607819Sym1 a6989586621679607817 a6989586621679607245 b6989586621679544674 :: TyFun (Either a6989586621679607245 b6989586621679544674) (Either a6989586621679607245 a6989586621679544673) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Fmap_6989586621679607791Sym1 a6989586621679607789 a6989586621679607245 :: TyFun (Either a6989586621679607245 a6989586621679544671) (Either a6989586621679607245 b6989586621679544672) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Traverse_6989586621680754442Sym0 :: TyFun (a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (Either a6989586621680753833 a6989586621680748240 ~> f6989586621680748239 (Either a6989586621680753833 b6989586621680748241)) -> Type) | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (TFHelper_6989586621679608113Sym1 a6989586621679608111 b6989586621679544701 :: TyFun (a6989586621679544700 ~> Either e6989586621679607274 b6989586621679544701) (Either e6989586621679607274 b6989586621679544701) -> Type) | |
Defined in Data.Singletons.Prelude.Monad.Internal Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Either_Sym1 a6989586621680430739 b6989586621680430705 :: TyFun (b6989586621680430705 ~> c6989586621680430704) (Either a6989586621680430703 b6989586621680430705 ~> c6989586621680430704) -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
SingI d => SingI (Either_Sym1 d b :: TyFun (b ~> c) (Either a b ~> c) -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods sing :: Sing (Either_Sym1 d b) # | |
SuppressUnusedWarnings (Traverse_6989586621680754442Sym1 a6989586621680754440 a6989586621680753833 :: TyFun (Either a6989586621680753833 a6989586621680748240) (f6989586621680748239 (Either a6989586621680753833 b6989586621680748241)) -> Type) | |
Defined in Data.Singletons.Prelude.Traversable Methods suppressUnusedWarnings :: () # | |
SuppressUnusedWarnings (Either_Sym2 a6989586621680430740 a6989586621680430739 :: TyFun (Either a6989586621680430703 b6989586621680430705) c6989586621680430704 -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods suppressUnusedWarnings :: () # | |
(SingI d1, SingI d2) => SingI (Either_Sym2 d1 d2 :: TyFun (Either a b) c -> Type) | |
Defined in Data.Singletons.Prelude.Either Methods sing :: Sing (Either_Sym2 d1 d2) # | |
(Random (t m r), Fact m, TensorCRT t Maybe r) => Random (CycRepPC t m r) Source # | |
Defined in Crypto.Lol.Cyclotomic.CycRep Methods randomR :: RandomGen g => (CycRepPC t m r, CycRepPC t m r) -> g -> (CycRepPC t m r, g) # random :: RandomGen g => g -> (CycRepPC t m r, g) # randomRs :: RandomGen g => (CycRepPC t m r, CycRepPC t m r) -> g -> [CycRepPC t m r] # randoms :: RandomGen g => g -> [CycRepPC t m r] # randomRIO :: (CycRepPC t m r, CycRepPC t m r) -> IO (CycRepPC t m r) # | |
(Fact m, CRTElt t r) => C (CycRepEC t m r) Source # | only for appropriate CRT representation |
(Fact m, CRTElt t r) => C (CycRepEC t m r) Source # | only for appropriate CRT representation (otherwise |
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680432540 :: Either a b) | |
Defined in Data.Singletons.Prelude.Either | |
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621680432542 :: Either a b) | |
Defined in Data.Singletons.Prelude.Either | |
type Apply (Compare_6989586621679390943Sym1 a6989586621679390941 :: TyFun (Either a b) Ordering -> Type) (a6989586621679390942 :: Either a b) | |
type Apply (Either_Sym2 a6989586621680430740 a6989586621680430739 :: TyFun (Either a b) c -> Type) (a6989586621680430741 :: Either a b) | |
Defined in Data.Singletons.Prelude.Either | |
type Product (arg :: Either a1 a2) | |
type Sum (arg :: Either a1 a2) | |
type Minimum (arg :: Either a1 a2) | |
type Maximum (arg :: Either a1 a2) | |
type Length (a2 :: Either a1 a6989586621680450743) | |
type Null (a2 :: Either a1 a6989586621680450742) | |
type ToList (arg :: Either a1 a2) | |
type Fold (arg :: Either a m) | |
type Pure (a :: k1) | |
type Fail arg | |
type Return (arg :: a) | |
type Sequence (arg :: Either a1 (m a2)) | |
type SequenceA (arg :: Either a1 (f a2)) | |
type Elem (arg1 :: a1) (arg2 :: Either a2 a1) | |
type Foldl1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) | |
type Foldr1 (arg1 :: a1 ~> (a1 ~> a1)) (arg2 :: Either a2 a1) | |
type FoldMap (a2 :: a6989586621680450730 ~> k2) (a3 :: Either a1 a6989586621680450730) | |
type (a2 :: k1) <$ (a3 :: Either a1 b6989586621679544674) | |
type Fmap (a2 :: a6989586621679544671 ~> b6989586621679544672) (a3 :: Either a1 a6989586621679544671) | |
Defined in Data.Singletons.Prelude.Monad.Internal | |
type (arg1 :: Either e a) <* (arg2 :: Either e b) | |
type (arg1 :: Either e a) *> (arg2 :: Either e b) | |
type (a1 :: Either e (a6989586621679544677 ~> b6989586621679544678)) <*> (a2 :: Either e a6989586621679544677) | |
Defined in Data.Singletons.Prelude.Monad.Internal type (a1 :: Either e (a6989586621679544677 ~> b6989586621679544678)) <*> (a2 :: Either e a6989586621679544677) = Apply (Apply (TFHelper_6989586621679608001Sym0 :: TyFun (Either e (a6989586621679544677 ~> b6989586621679544678)) (Either e a6989586621679544677 ~> Either e b6989586621679544678) -> Type) a1) a2 | |
type (arg1 :: Either e a) >> (arg2 :: Either e b) | |
type (a1 :: Either e a6989586621679544700) >>= (a2 :: a6989586621679544700 ~> Either e b6989586621679544701) | |
Defined in Data.Singletons.Prelude.Monad.Internal type (a1 :: Either e a6989586621679544700) >>= (a2 :: a6989586621679544700 ~> Either e b6989586621679544701) = Apply (Apply (TFHelper_6989586621679608113Sym0 :: TyFun (Either e a6989586621679544700) ((a6989586621679544700 ~> Either e b6989586621679544701) ~> Either e b6989586621679544701) -> Type) a1) a2 | |
type MapM (arg1 :: a1 ~> m b) (arg2 :: Either a2 a1) | |
type Traverse (a2 :: a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (a3 :: Either a1 a6989586621680748240) | |
Defined in Data.Singletons.Prelude.Traversable type Traverse (a2 :: a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (a3 :: Either a1 a6989586621680748240) = Apply (Apply (Traverse_6989586621680754442Sym0 :: TyFun (a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (Either a1 a6989586621680748240 ~> f6989586621680748239 (Either a1 b6989586621680748241)) -> Type) a2) a3 | |
type Foldl' (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) | |
type Foldl (arg1 :: b ~> (a1 ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) | |
type Foldr' (arg1 :: a1 ~> (b ~> b)) (arg2 :: b) (arg3 :: Either a2 a1) | |
type Foldr (a2 :: a6989586621680450731 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Either a1 a6989586621680450731) | |
Defined in Data.Singletons.Prelude.Foldable | |
type LiftA2 (arg1 :: a ~> (b ~> c)) (arg2 :: Either e a) (arg3 :: Either e b) | |
type Rep1 (Either a :: Type -> Type) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 (Either a :: Type -> Type) = D1 (MetaData "Either" "Data.Either" "base" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1)) | |
type Apply (RightsSym0 :: TyFun [Either a b] [b] -> Type) (a6989586621680432566 :: [Either a b]) | |
Defined in Data.Singletons.Prelude.Either | |
type Apply (LeftsSym0 :: TyFun [Either a b] [a] -> Type) (a6989586621680432571 :: [Either a b]) | |
type Apply (Traverse_6989586621680754442Sym1 a6989586621680754440 a2 :: TyFun (Either a2 a1) (f (Either a2 b)) -> Type) (a6989586621680754441 :: Either a2 a1) | |
type Rep (Either a b) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep (Either a b) = D1 (MetaData "Either" "Data.Either" "base" False) (C1 (MetaCons "Left" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) :+: C1 (MetaCons "Right" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 b))) | |
data Sing (c :: Either a b) | |
type Demote (Either a b) | |
type Show_ (arg :: Either a b) | |
type Sconcat (arg :: NonEmpty (Either a b)) | |
type ShowList (arg1 :: [Either a b]) arg2 | |
type (a2 :: Either a1 b) <> (a3 :: Either a1 b) | |
type Min (arg1 :: Either a b) (arg2 :: Either a b) | |
type Max (arg1 :: Either a b) (arg2 :: Either a b) | |
type (arg1 :: Either a b) >= (arg2 :: Either a b) | |
type (arg1 :: Either a b) > (arg2 :: Either a b) | |
type (arg1 :: Either a b) <= (arg2 :: Either a b) | |
type (arg1 :: Either a b) < (arg2 :: Either a b) | |
type Compare (a2 :: Either a1 b) (a3 :: Either a1 b) | |
type (x :: Either a b) /= (y :: Either a b) | |
type (a2 :: Either a1 b1) == (b2 :: Either a1 b1) | |
Defined in Data.Singletons.Prelude.Eq | |
type ShowsPrec a2 (a3 :: Either a1 b) a4 | |
type Apply (Pure_6989586621679607989Sym0 :: TyFun a (Either e6989586621679607257 a) -> Type) (a6989586621679607988 :: a) | |
type Apply (LeftSym0 :: TyFun a (Either a b6989586621679074206) -> Type) (t6989586621679294647 :: a) | |
type Apply (RightSym0 :: TyFun b (Either a6989586621679074205 b) -> Type) (t6989586621679294649 :: b) | |
type Apply (Let6989586621679811171ASym0 :: TyFun k1 (Either a6989586621679074205 k1) -> Type) (wild_69895866216798105616989586621679811170 :: k1) | |
Defined in Data.Singletons.Prelude.Semigroup.Internal | |
type Apply (ShowsPrec_6989586621680280907Sym0 :: TyFun Nat (Either a6989586621679074205 b6989586621679074206 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680280904 :: Nat) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680280907Sym0 :: TyFun Nat (Either a6989586621679074205 b6989586621679074206 ~> (Symbol ~> Symbol)) -> Type) (a6989586621680280904 :: Nat) = (ShowsPrec_6989586621680280907Sym1 a6989586621680280904 a6989586621679074205 b6989586621679074206 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Symbol ~> Symbol) -> Type) | |
type Apply (TFHelper_6989586621679607819Sym0 :: TyFun a6989586621679544673 (Either a6989586621679607245 b6989586621679544674 ~> Either a6989586621679607245 a6989586621679544673) -> Type) (a6989586621679607817 :: a6989586621679544673) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (TFHelper_6989586621679607819Sym0 :: TyFun a6989586621679544673 (Either a6989586621679607245 b6989586621679544674 ~> Either a6989586621679607245 a6989586621679544673) -> Type) (a6989586621679607817 :: a6989586621679544673) = (TFHelper_6989586621679607819Sym1 a6989586621679607817 a6989586621679607245 b6989586621679544674 :: TyFun (Either a6989586621679607245 b6989586621679544674) (Either a6989586621679607245 a6989586621679544673) -> Type) | |
type Apply (PartitionEithersSym0 :: TyFun [Either a b] ([a], [b]) -> Type) (a6989586621680432546 :: [Either a b]) | |
Defined in Data.Singletons.Prelude.Either | |
type Apply (Compare_6989586621679390943Sym0 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Either a6989586621679074205 b6989586621679074206 ~> Ordering) -> Type) (a6989586621679390941 :: Either a6989586621679074205 b6989586621679074206) | |
Defined in Data.Singletons.Prelude.Ord type Apply (Compare_6989586621679390943Sym0 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Either a6989586621679074205 b6989586621679074206 ~> Ordering) -> Type) (a6989586621679390941 :: Either a6989586621679074205 b6989586621679074206) = Compare_6989586621679390943Sym1 a6989586621679390941 | |
type Apply (Fmap_6989586621679607791Sym0 :: TyFun (a6989586621679544671 ~> b6989586621679544672) (Either a6989586621679607245 a6989586621679544671 ~> Either a6989586621679607245 b6989586621679544672) -> Type) (a6989586621679607789 :: a6989586621679544671 ~> b6989586621679544672) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (Fmap_6989586621679607791Sym0 :: TyFun (a6989586621679544671 ~> b6989586621679544672) (Either a6989586621679607245 a6989586621679544671 ~> Either a6989586621679607245 b6989586621679544672) -> Type) (a6989586621679607789 :: a6989586621679544671 ~> b6989586621679544672) = (Fmap_6989586621679607791Sym1 a6989586621679607789 a6989586621679607245 :: TyFun (Either a6989586621679607245 a6989586621679544671) (Either a6989586621679607245 b6989586621679544672) -> Type) | |
type Apply (TFHelper_6989586621679608001Sym0 :: TyFun (Either e6989586621679607257 (a6989586621679544677 ~> b6989586621679544678)) (Either e6989586621679607257 a6989586621679544677 ~> Either e6989586621679607257 b6989586621679544678) -> Type) (a6989586621679607999 :: Either e6989586621679607257 (a6989586621679544677 ~> b6989586621679544678)) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (TFHelper_6989586621679608001Sym0 :: TyFun (Either e6989586621679607257 (a6989586621679544677 ~> b6989586621679544678)) (Either e6989586621679607257 a6989586621679544677 ~> Either e6989586621679607257 b6989586621679544678) -> Type) (a6989586621679607999 :: Either e6989586621679607257 (a6989586621679544677 ~> b6989586621679544678)) = TFHelper_6989586621679608001Sym1 a6989586621679607999 | |
type Apply (ShowsPrec_6989586621680280907Sym1 a6989586621680280904 a6989586621679074205 b6989586621679074206 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Symbol ~> Symbol) -> Type) (a6989586621680280905 :: Either a6989586621679074205 b6989586621679074206) | |
Defined in Data.Singletons.Prelude.Show type Apply (ShowsPrec_6989586621680280907Sym1 a6989586621680280904 a6989586621679074205 b6989586621679074206 :: TyFun (Either a6989586621679074205 b6989586621679074206) (Symbol ~> Symbol) -> Type) (a6989586621680280905 :: Either a6989586621679074205 b6989586621679074206) = ShowsPrec_6989586621680280907Sym2 a6989586621680280904 a6989586621680280905 | |
type Apply (TFHelper_6989586621679608113Sym0 :: TyFun (Either e6989586621679607274 a6989586621679544700) ((a6989586621679544700 ~> Either e6989586621679607274 b6989586621679544701) ~> Either e6989586621679607274 b6989586621679544701) -> Type) (a6989586621679608111 :: Either e6989586621679607274 a6989586621679544700) | |
Defined in Data.Singletons.Prelude.Monad.Internal type Apply (TFHelper_6989586621679608113Sym0 :: TyFun (Either e6989586621679607274 a6989586621679544700) ((a6989586621679544700 ~> Either e6989586621679607274 b6989586621679544701) ~> Either e6989586621679607274 b6989586621679544701) -> Type) (a6989586621679608111 :: Either e6989586621679607274 a6989586621679544700) = (TFHelper_6989586621679608113Sym1 a6989586621679608111 b6989586621679544701 :: TyFun (a6989586621679544700 ~> Either e6989586621679607274 b6989586621679544701) (Either e6989586621679607274 b6989586621679544701) -> Type) | |
type Apply (Either_Sym0 :: TyFun (a6989586621680430703 ~> c6989586621680430704) ((b6989586621680430705 ~> c6989586621680430704) ~> (Either a6989586621680430703 b6989586621680430705 ~> c6989586621680430704)) -> Type) (a6989586621680430739 :: a6989586621680430703 ~> c6989586621680430704) | |
Defined in Data.Singletons.Prelude.Either type Apply (Either_Sym0 :: TyFun (a6989586621680430703 ~> c6989586621680430704) ((b6989586621680430705 ~> c6989586621680430704) ~> (Either a6989586621680430703 b6989586621680430705 ~> c6989586621680430704)) -> Type) (a6989586621680430739 :: a6989586621680430703 ~> c6989586621680430704) = (Either_Sym1 a6989586621680430739 b6989586621680430705 :: TyFun (b6989586621680430705 ~> c6989586621680430704) (Either a6989586621680430703 b6989586621680430705 ~> c6989586621680430704) -> Type) | |
type Apply (Fmap_6989586621679607791Sym1 a6989586621679607789 a1 :: TyFun (Either a1 a2) (Either a1 b) -> Type) (a6989586621679607790 :: Either a1 a2) | |
type Apply (TFHelper_6989586621679607819Sym1 a6989586621679607817 a1 b :: TyFun (Either a1 b) (Either a1 a2) -> Type) (a6989586621679607818 :: Either a1 b) | |
type Apply (TFHelper_6989586621679608001Sym1 a6989586621679607999 :: TyFun (Either e a) (Either e b) -> Type) (a6989586621679608000 :: Either e a) | |
type Apply (TFHelper_6989586621679608113Sym1 a6989586621679608111 b :: TyFun (a ~> Either e b) (Either e b) -> Type) (a6989586621679608112 :: a ~> Either e b) | |
type Apply (Traverse_6989586621680754442Sym0 :: TyFun (a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (Either a6989586621680753833 a6989586621680748240 ~> f6989586621680748239 (Either a6989586621680753833 b6989586621680748241)) -> Type) (a6989586621680754440 :: a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) | |
Defined in Data.Singletons.Prelude.Traversable type Apply (Traverse_6989586621680754442Sym0 :: TyFun (a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) (Either a6989586621680753833 a6989586621680748240 ~> f6989586621680748239 (Either a6989586621680753833 b6989586621680748241)) -> Type) (a6989586621680754440 :: a6989586621680748240 ~> f6989586621680748239 b6989586621680748241) = (Traverse_6989586621680754442Sym1 a6989586621680754440 a6989586621680753833 :: TyFun (Either a6989586621680753833 a6989586621680748240) (f6989586621680748239 (Either a6989586621680753833 b6989586621680748241)) -> Type) | |
type Apply (Either_Sym1 a6989586621680430739 b6989586621680430705 :: TyFun (b6989586621680430705 ~> c6989586621680430704) (Either a6989586621680430703 b6989586621680430705 ~> c6989586621680430704) -> Type) (a6989586621680430740 :: b6989586621680430705 ~> c6989586621680430704) | |
Defined in Data.Singletons.Prelude.Either type Apply (Either_Sym1 a6989586621680430739 b6989586621680430705 :: TyFun (b6989586621680430705 ~> c6989586621680430704) (Either a6989586621680430703 b6989586621680430705 ~> c6989586621680430704) -> Type) (a6989586621680430740 :: b6989586621680430705 ~> c6989586621680430704) = Either_Sym2 a6989586621680430739 a6989586621680430740 |
File and directory names are values of type String
, whose precise
meaning is operating system dependent. Files can be opened, yielding a
handle which can then be used to operate on the contents of that file.
error :: HasCallStack => [Char] -> a #
error
stops execution and displays an error message.
(=<<) :: Monad m => (a -> m b) -> m a -> m b infixr 1 #
Same as >>=
, but with the arguments interchanged.
sequence_ :: (Foldable t, Monad m) => t (m a) -> m () #
Evaluate each monadic action in the structure from left to right,
and ignore the results. For a version that doesn't ignore the
results see sequence
.
As of base 4.8.0.0, sequence_
is just sequenceA_
, specialized
to Monad
.
const x
is a unary function which evaluates to x
for all inputs.
>>>
const 42 "hello"
42
>>>
map (const 42) [0..3]
[42,42,42,42]
read :: Read a => String -> a #
The read
function reads input from a string, which must be
completely consumed by the input process. read
fails with an error
if the
parse is unsuccessful, and it is therefore discouraged from being used in
real applications. Use readMaybe
or readEither
for safe alternatives.
>>>
read "123" :: Int
123
>>>
read "hello" :: Int
*** Exception: Prelude.read: no parse
appendFile :: FilePath -> String -> IO () #
The computation appendFile
file str
function appends the string str
,
to the file file
.
Note that writeFile
and appendFile
write a literal string
to a file. To write a value of any printable type, as with print
,
use the show
function to convert the value to a string first.
main = appendFile "squares" (show [(x,x*x) | x <- [0,0.1..2]])
writeFile :: FilePath -> String -> IO () #
The computation writeFile
file str
function writes the string str
,
to the file file
.
readFile :: FilePath -> IO String #
The readFile
function reads a file and
returns the contents of the file as a string.
The file is read lazily, on demand, as with getContents
.
interact :: (String -> String) -> IO () #
The interact
function takes a function of type String->String
as its argument. The entire input from the standard input device is
passed to this function as its argument, and the resulting string is
output on the standard output device.
getContents :: IO String #
The getContents
operation returns all user input as a single string,
which is read lazily as it is needed
(same as hGetContents
stdin
).
userError :: String -> IOError #
Construct an IOException
value with a string describing the error.
The fail
method of the IO
instance of the Monad
class raises a
userError
, thus:
instance Monad IO where ... fail s = ioError (userError s)
type IOError = IOException #
The Haskell 2010 type for exceptions in the IO
monad.
Any I/O operation may raise an IOException
instead of returning a result.
For a more general type of exception, including also those that arise
in pure code, see Exception
.
In Haskell 2010, this is an opaque type.
all :: Foldable t => (a -> Bool) -> t a -> Bool #
Determines whether all elements of the structure satisfy the predicate.
any :: Foldable t => (a -> Bool) -> t a -> Bool #
Determines whether any element of the structure satisfies the predicate.
concatMap :: Foldable t => (a -> [b]) -> t a -> [b] #
Map a function over all the elements of a container and concatenate the resulting lists.
concat :: Foldable t => t [a] -> [a] #
The concatenation of all the elements of a container of lists.
words
breaks a string up into a list of words, which were delimited
by white space.
>>>
words "Lorem ipsum\ndolor"
["Lorem","ipsum","dolor"]
lines
breaks a string up into a list of strings at newline
characters. The resulting strings do not contain newlines.
Note that after splitting the string at newline characters, the last part of the string is considered a line even if it doesn't end with a newline. For example,
>>>
lines ""
[]
>>>
lines "\n"
[""]
>>>
lines "one"
["one"]
>>>
lines "one\n"
["one"]
>>>
lines "one\n\n"
["one",""]
>>>
lines "one\ntwo"
["one","two"]
>>>
lines "one\ntwo\n"
["one","two"]
Thus
contains at least as many elements as newlines in lines
ss
.
either :: (a -> c) -> (b -> c) -> Either a b -> c #
Case analysis for the Either
type.
If the value is
, apply the first function to Left
aa
;
if it is
, apply the second function to Right
bb
.
Examples
We create two values of type
, one using the
Either
String
Int
Left
constructor and another using the Right
constructor. Then
we apply "either" the length
function (if we have a String
)
or the "times-two" function (if we have an Int
):
>>>
let s = Left "foo" :: Either String Int
>>>
let n = Right 3 :: Either String Int
>>>
either length (*2) s
3>>>
either length (*2) n
6
The lex
function reads a single lexeme from the input, discarding
initial white space, and returning the characters that constitute the
lexeme. If the input string contains only white space, lex
returns a
single successful `lexeme' consisting of the empty string. (Thus
.) If there is no legal lexeme at the
beginning of the input string, lex
"" = [("","")]lex
fails (i.e. returns []
).
This lexer is not completely faithful to the Haskell lexical syntax in the following respects:
- Qualified names are not handled properly
- Octal and hexadecimal numerics are not recognized as a single token
- Comments are not treated properly
showString :: String -> ShowS #
utility function converting a String
to a show function that
simply prepends the string unchanged.
utility function converting a Char
to a show function that
simply prepends the character unchanged.
unzip :: [(a, b)] -> ([a], [b]) #
unzip
transforms a list of pairs into a list of first components
and a list of second components.
(!!) :: [a] -> Int -> a infixl 9 #
List index (subscript) operator, starting from 0.
It is an instance of the more general genericIndex
,
which takes an index of any integral type.
lookup :: Eq a => a -> [(a, b)] -> Maybe b #
lookup
key assocs
looks up a key in an association list.
break :: (a -> Bool) -> [a] -> ([a], [a]) #
break
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
do not satisfy p
and second element is the remainder of the list:
break (> 3) [1,2,3,4,1,2,3,4] == ([1,2,3],[4,1,2,3,4]) break (< 9) [1,2,3] == ([],[1,2,3]) break (> 9) [1,2,3] == ([1,2,3],[])
span :: (a -> Bool) -> [a] -> ([a], [a]) #
span
, applied to a predicate p
and a list xs
, returns a tuple where
first element is longest prefix (possibly empty) of xs
of elements that
satisfy p
and second element is the remainder of the list:
span (< 3) [1,2,3,4,1,2,3,4] == ([1,2],[3,4,1,2,3,4]) span (< 9) [1,2,3] == ([1,2,3],[]) span (< 0) [1,2,3] == ([],[1,2,3])
splitAt :: Int -> [a] -> ([a], [a]) #
splitAt
n xs
returns a tuple where first element is xs
prefix of
length n
and second element is the remainder of the list:
splitAt 6 "Hello World!" == ("Hello ","World!") splitAt 3 [1,2,3,4,5] == ([1,2,3],[4,5]) splitAt 1 [1,2,3] == ([1],[2,3]) splitAt 3 [1,2,3] == ([1,2,3],[]) splitAt 4 [1,2,3] == ([1,2,3],[]) splitAt 0 [1,2,3] == ([],[1,2,3]) splitAt (-1) [1,2,3] == ([],[1,2,3])
It is equivalent to (
when take
n xs, drop
n xs)n
is not _|_
(splitAt _|_ xs = _|_
).
splitAt
is an instance of the more general genericSplitAt
,
in which n
may be of any integral type.
drop
n xs
returns the suffix of xs
after the first n
elements, or []
if n >
:length
xs
drop 6 "Hello World!" == "World!" drop 3 [1,2,3,4,5] == [4,5] drop 3 [1,2] == [] drop 3 [] == [] drop (-1) [1,2] == [1,2] drop 0 [1,2] == [1,2]
It is an instance of the more general genericDrop
,
in which n
may be of any integral type.
take
n
, applied to a list xs
, returns the prefix of xs
of length n
, or xs
itself if n >
:length
xs
take 5 "Hello World!" == "Hello" take 3 [1,2,3,4,5] == [1,2,3] take 3 [1,2] == [1,2] take 3 [] == [] take (-1) [1,2] == [] take 0 [1,2] == []
It is an instance of the more general genericTake
,
in which n
may be of any integral type.
takeWhile :: (a -> Bool) -> [a] -> [a] #
takeWhile
, applied to a predicate p
and a list xs
, returns the
longest prefix (possibly empty) of xs
of elements that satisfy p
:
takeWhile (< 3) [1,2,3,4,1,2,3,4] == [1,2] takeWhile (< 9) [1,2,3] == [1,2,3] takeWhile (< 0) [1,2,3] == []
cycle
ties a finite list into a circular one, or equivalently,
the infinite repetition of the original list. It is the identity
on infinite lists.
replicate :: Int -> a -> [a] #
replicate
n x
is a list of length n
with x
the value of
every element.
It is an instance of the more general genericReplicate
,
in which n
may be of any integral type.
Return all the elements of a list except the last one. The list must be non-empty.
maybe :: b -> (a -> b) -> Maybe a -> b #
The maybe
function takes a default value, a function, and a Maybe
value. If the Maybe
value is Nothing
, the function returns the
default value. Otherwise, it applies the function to the value inside
the Just
and returns the result.
Examples
Basic usage:
>>>
maybe False odd (Just 3)
True
>>>
maybe False odd Nothing
False
Read an integer from a string using readMaybe
. If we succeed,
return twice the integer; that is, apply (*2)
to it. If instead
we fail to parse an integer, return 0
by default:
>>>
import Text.Read ( readMaybe )
>>>
maybe 0 (*2) (readMaybe "5")
10>>>
maybe 0 (*2) (readMaybe "")
0
Apply show
to a Maybe Int
. If we have Just n
, we want to show
the underlying Int
n
. But if we have Nothing
, we return the
empty string instead of (for example) "Nothing":
>>>
maybe "" show (Just 5)
"5">>>
maybe "" show Nothing
""
uncurry :: (a -> b -> c) -> (a, b) -> c #
uncurry
converts a curried function to a function on pairs.
Examples
>>>
uncurry (+) (1,2)
3
>>>
uncurry ($) (show, 1)
"1"
>>>
map (uncurry max) [(1,2), (3,4), (6,8)]
[2,4,8]
until :: (a -> Bool) -> (a -> a) -> a -> a #
yields the result of applying until
p ff
until p
holds.
($!) :: (a -> b) -> a -> b infixr 0 #
Strict (call-by-value) application operator. It takes a function and an argument, evaluates the argument to weak head normal form (WHNF), then calls the function with that value.
flip :: (a -> b -> c) -> b -> a -> c #
takes its (first) two arguments in the reverse order of flip
ff
.
>>>
flip (++) "hello" "world"
"worldhello"
undefined :: HasCallStack => a #
approxRational :: (C a, C a) => a -> a -> Rational #
TODO: Should be moved to a continued fraction module.
splitFraction :: (C a, C b) => a -> (b, a) #
fieldPower :: (C a, C b) => b -> a -> a #
A prefix function of '(Algebra.Field.^-)'. It has a generalised exponent.
ringPower :: (C a, C b) => b -> a -> a #
A prefix function of '(Algebra.Ring.^)' with a parameter order that fits the needs of partial application and function composition. It has generalised exponent.
See: Argument order of expNat
on
http://www.haskell.org/pipermail/haskell-cafe/2006-September/018022.html
fromIntegral :: (C a, C b) => a -> b #
toRational :: C a => a -> Rational #
Lossless conversion from any representation of a rational to Rational
fromRational :: C a => Rational -> a #
Needed to work around shortcomings in GHC.
fromRational' :: C a => Rational -> a #
denominator :: T a -> a #
extendedEuclid :: (C a, C a) => (a -> a -> (a, a)) -> a -> a -> (a, (a, a)) #
The Greatest Common Divisor is defined by:
gcd x y == gcd y x divides z x && divides z y ==> divides z (gcd x y) (specification) divides (gcd x y) x
extendedGCD :: C a => a -> a -> (a, (a, a)) #
Compute the greatest common divisor and solve a respective Diophantine equation.
(g,(a,b)) = extendedGCD x y ==> g==a*x+b*y && g == gcd x y
TODO: This method is not appropriate for the PID class, because there are rings like the one of the multivariate polynomials, where for all x and y greatest common divisors of x and y exist, but they cannot be represented as a linear combination of x and y. TODO: The definition of extendedGCD does not return the canonical associate.
stdAssociate :: C a => a -> a #
stdUnitInv :: C a => a -> a #
fromInteger :: C a => Integer -> a #
Sum up all elements of a non-empty list. This avoids including a zero which is useful for types where no universal zero is available. ToDo: Should have NonEmpty type.
Sum up all elements of a list. An empty list yields zero.
This function is inappropriate for number types like Peano.
Maybe we should make sum
a method of Additive.
This would also make lengthLeft
and lengthRight
superfluous.
subtract :: C a => a -> a -> a #
subtract
is (-)
with swapped operand order.
This is the operand order which will be needed in most cases
of partial application.
ifThenElse :: Bool -> a -> a -> a #
The same as if'
, but the name is chosen
such that it can be used for GHC-7.0's rebindable if-then-else syntax.
64-bit signed integer type
Instances
Complex
Newtype wrapper (with slightly different instances) for
Number.Complex
.
Instances
Transcendental a => CRTrans Maybe (Complex a) Source # | For testing ergonomics, we also have a |
Transcendental a => CRTrans Identity (Complex a) Source # | Complex numbers have |
Eq a => Eq (Complex a) Source # | |
Show a => Show (Complex a) Source # | |
Random a => Random (Complex a) Source # | |
Defined in Crypto.Lol.Types.Unsafe.Complex | |
NFData a => NFData (Complex a) Source # | |
Defined in Crypto.Lol.Types.Unsafe.Complex | |
C a => C (Complex a) Source # | |
Field a => C (Complex a) Source # | Custom instance replacing the one provided by numeric prelude: it
always returns 0 as the remainder of a division. (The NP instance
sometimes has precision issues, because it yields nonzero
remainders, which is a problem for |
C a => C (Complex a) Source # | |
C a => C (Complex a) Source # | |
Defined in Crypto.Lol.Types.Unsafe.Complex | |
C a => C (Complex a) Source # | |
Transcendental a => CRTEmbed (Complex a) Source # | Self-embed |
ApproxEqual (Complex Double) Source # | |
Show (ArgType (Complex Double)) Source # | |
type CRTExt (Complex a) Source # | |
Defined in Crypto.Lol.CRTrans |
roundComplex :: (RealRing a, ToInteger b) => Complex a -> (b, b) Source #
Rounds the real and imaginary components to the nearest integer.
cis :: Transcendental a => a -> Complex a Source #
cis
\(t\) is a complex value with magnitude 1 and phase \(t \bmod 2\cdot\pi\)).
fromReal :: Additive a => a -> Complex a Source #
Embeds a scalar as the real component of a complex number.
Factored
module Crypto.Lol.Factored
Miscellaneous
rescaleMod :: forall a b. (Mod a, Mod b, ModRep a ~ ModRep b, Lift a (ModRep b), Ring b) => a -> b Source #
A default implementation of rescaling for Mod
types.
roundCoset :: forall zp z r. (Mod zp, z ~ ModRep zp, Lift zp z, RealField r) => zp -> r -> z Source #
Deterministically round to the nearest value in the desired coset.
pureT :: Applicative f => Tagged t a -> TaggedT t f a Source #
Apply any applicative to a Tagged
value.
withWitness :: forall n r. (SingI n => Tagged n r) -> Sing n -> r Source #
Use a singleton as a witness to extract a value from a Tagged
value.
withWitnessT :: forall n mon r. (SingI n => TaggedT n mon r) -> Sing n -> mon r Source #
Transformer version of withWitness
.
module Data.Functor.Trans.Tagged
module Data.Proxy