singletons-base
Copyright(C) 2013 Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageGHC2021

Prelude.Singletons

Description

Mimics the Haskell Prelude, but with singleton types. Includes the basic singleton definitions. Note: This is currently very incomplete!

Because many of these definitions are produced by Template Haskell, it is not possible to create proper Haddock documentation. Also, please excuse the apparent repeated variable names. This is due to an interaction between Template Haskell and Haddock.

Synopsis

Basic singleton definitions

(@@) :: forall k1 k2 (f :: k1 ~> k2) (t :: k1). Sing f -> Sing t -> Sing (f @@ t) #

pattern FromSing :: forall k (a :: k). SingKind k => Sing a -> Demote k #

pattern SLambda2 :: forall {a1} {a2} {b} (f :: a1 ~> (a2 ~> b)). SingFunction2 f -> Sing f #

pattern SLambda3 :: forall {a1} {a2} {a3} {b} (f :: a1 ~> (a2 ~> (a3 ~> b))). SingFunction3 f -> Sing f #

pattern SLambda4 :: forall {a1} {a2} {a3} {a4} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> b)))). SingFunction4 f -> Sing f #

pattern SLambda5 :: forall {a1} {a2} {a3} {a4} {a5} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> b))))). SingFunction5 f -> Sing f #

pattern SLambda6 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> b)))))). SingFunction6 f -> Sing f #

pattern SLambda7 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {a7} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> b))))))). SingFunction7 f -> Sing f #

pattern SLambda8 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {a7} {a8} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> (a8 ~> b)))))))). SingFunction8 f -> Sing f #

pattern Sing :: forall k (a :: k). () => SingI a => Sing a #

applySing2 :: forall {a1} {a2} {b} (f :: a1 ~> (a2 ~> b)). Sing f -> SingFunction2 f #

applySing3 :: forall {a1} {a2} {a3} {b} (f :: a1 ~> (a2 ~> (a3 ~> b))). Sing f -> SingFunction3 f #

applySing4 :: forall {a1} {a2} {a3} {a4} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> b)))). Sing f -> SingFunction4 f #

applySing5 :: forall {a1} {a2} {a3} {a4} {a5} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> b))))). Sing f -> SingFunction5 f #

applySing6 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> b)))))). Sing f -> SingFunction6 f #

applySing7 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {a7} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> b))))))). Sing f -> SingFunction7 f #

applySing8 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {a7} {a8} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> (a8 ~> b)))))))). Sing f -> SingFunction8 f #

demote :: forall {k} (a :: k). (SingKind k, SingI a) => Demote k #

demote1 :: forall {k1} {k2} (f :: k1 -> k2) (x :: k1). (SingKind k2, SingI1 f, SingI x) => Demote k2 #

demote2 :: forall {k1} {k2} {k3} (f :: k1 -> k2 -> k3) (x :: k1) (y :: k2). (SingKind k3, SingI2 f, SingI x, SingI y) => Demote k3 #

sing1 :: forall {k1} {k} (f :: k1 -> k) (x :: k1). (SingI1 f, SingI x) => Sing (f x) #

sing2 :: forall {k1} {k2} {k} (f :: k1 -> k2 -> k) (x :: k1) (y :: k2). (SingI2 f, SingI x, SingI y) => Sing (f x y) #

singByProxy :: forall {k} (a :: k) proxy. SingI a => proxy a -> Sing a #

singByProxy# :: forall {k} (a :: k). SingI a => Proxy# a -> Sing a #

singByProxy1 :: forall {k1} {k} (f :: k1 -> k) (x :: k1) proxy. (SingI1 f, SingI x) => proxy (f x) -> Sing (f x) #

singByProxy1# :: forall {k1} {k} (f :: k1 -> k) (x :: k1). (SingI1 f, SingI x) => Proxy# (f x) -> Sing (f x) #

singByProxy2 :: forall {k1} {k2} {k} (f :: k1 -> k2 -> k) (x :: k1) (y :: k2) proxy. (SingI2 f, SingI x, SingI y) => proxy (f x y) -> Sing (f x y) #

singByProxy2# :: forall {k1} {k2} {k} (f :: k1 -> k2 -> k) (x :: k1) (y :: k2). (SingI2 f, SingI x, SingI y) => Proxy# (f x y) -> Sing (f x y) #

singFun1 :: forall {a1} {b} (f :: a1 ~> b). SingFunction1 f -> Sing f #

singFun2 :: forall {a1} {a2} {b} (f :: a1 ~> (a2 ~> b)). SingFunction2 f -> Sing f #

singFun3 :: forall {a1} {a2} {a3} {b} (f :: a1 ~> (a2 ~> (a3 ~> b))). SingFunction3 f -> Sing f #

singFun4 :: forall {a1} {a2} {a3} {a4} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> b)))). SingFunction4 f -> Sing f #

singFun5 :: forall {a1} {a2} {a3} {a4} {a5} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> b))))). SingFunction5 f -> Sing f #

singFun6 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> b)))))). SingFunction6 f -> Sing f #

singFun7 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {a7} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> b))))))). SingFunction7 f -> Sing f #

singFun8 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {a7} {a8} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> (a8 ~> b)))))))). SingFunction8 f -> Sing f #

singInstance :: forall k (a :: k). Sing a -> SingInstance a #

singThat :: forall k (a :: k). (SingKind k, SingI a) => (Demote k -> Bool) -> Maybe (Sing a) #

singThat1 :: forall k1 k2 (f :: k1 -> k2) (x :: k1). (SingKind k2, SingI1 f, SingI x) => (Demote k2 -> Bool) -> Maybe (Sing (f x)) #

singThat2 :: forall k1 k2 k3 (f :: k1 -> k2 -> k3) (x :: k1) (y :: k2). (SingKind k3, SingI2 f, SingI x, SingI y) => (Demote k3 -> Bool) -> Maybe (Sing (f x y)) #

unSingFun1 :: forall {a1} {b} (f :: a1 ~> b). Sing f -> SingFunction1 f #

unSingFun2 :: forall {a1} {a2} {b} (f :: a1 ~> (a2 ~> b)). Sing f -> SingFunction2 f #

unSingFun3 :: forall {a1} {a2} {a3} {b} (f :: a1 ~> (a2 ~> (a3 ~> b))). Sing f -> SingFunction3 f #

unSingFun4 :: forall {a1} {a2} {a3} {a4} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> b)))). Sing f -> SingFunction4 f #

unSingFun5 :: forall {a1} {a2} {a3} {a4} {a5} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> b))))). Sing f -> SingFunction5 f #

unSingFun6 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> b)))))). Sing f -> SingFunction6 f #

unSingFun7 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {a7} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> b))))))). Sing f -> SingFunction7 f #

unSingFun8 :: forall {a1} {a2} {a3} {a4} {a5} {a6} {a7} {a8} {b} (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> (a8 ~> b)))))))). Sing f -> SingFunction8 f #

usingSingI1 :: forall {k1} {k} (f :: k1 -> k) (x :: k1) r. (SingI1 f, SingI x) => (SingI (f x) => r) -> r #

usingSingI2 :: forall {k1} {k2} {k} (f :: k1 -> k2 -> k) (x :: k1) (y :: k2) r. (SingI2 f, SingI x, SingI y) => (SingI (f x y) => r) -> r #

withSing :: forall {k} (a :: k) b. SingI a => (Sing a -> b) -> b #

withSing1 :: forall {k1} {k} (f :: k1 -> k) (x :: k1) b. (SingI1 f, SingI x) => (Sing (f x) -> b) -> b #

withSing2 :: forall {k1} {k2} {k} (f :: k1 -> k2 -> k) (x :: k1) (y :: k2) b. (SingI2 f, SingI x, SingI y) => (Sing (f x y) -> b) -> b #

withSingI :: forall {k} (n :: k) r. Sing n -> (SingI n => r) -> r #

withSomeSing :: SingKind k => Demote k -> (forall (a :: k). Sing a -> r) -> r #

data Proxy (t :: k) #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the undefined :: a idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 

Instances

Instances details
Generic1 (Proxy :: k -> Type) # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))

Methods

from1 :: forall (a :: k). Proxy a -> Rep1 (Proxy :: k -> Type) a #

to1 :: forall (a :: k). Rep1 (Proxy :: k -> Type) a -> Proxy a #

Eq1 (Proxy :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Ord1 (Proxy :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

Read1 (Proxy :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

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

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

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

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

Contravariant (Proxy :: Type -> Type) # 
Instance details

Defined in Data.Functor.Contravariant

Methods

contramap :: (a' -> a) -> Proxy a -> Proxy a' #

(>$) :: b -> Proxy b -> Proxy a #

NFData1 (Proxy :: Type -> Type) #

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Proxy a -> () #

Alternative (Proxy :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

Applicative (Proxy :: Type -> Type) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

pure :: a -> Proxy a #

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

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

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

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

Functor (Proxy :: Type -> Type) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

Monad (Proxy :: Type -> Type) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

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

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

return :: a -> Proxy a #

MonadPlus (Proxy :: Type -> Type) #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

MonadZip (Proxy :: Type -> Type) #

Since: ghc-internal-4.9.0.0

Instance details

Defined in GHC.Internal.Control.Monad.Zip

Methods

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

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

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

Foldable (Proxy :: Type -> Type) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldMap' :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Traversable

Methods

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

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

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

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

Hashable1 (Proxy :: Type -> Type) # 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

PAlternative (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Empty 
Instance details

Defined in Data.Proxy.Singletons

type Empty
type (a2 :: Proxy a1) <|> (a3 :: Proxy a1) 
Instance details

Defined in Data.Proxy.Singletons

type (a2 :: Proxy a1) <|> (a3 :: Proxy a1)
PApplicative (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Proxy.Singletons

type Pure (a2 :: a1)
type (a2 :: Proxy (a1 ~> b)) <*> (a3 :: Proxy a1) 
Instance details

Defined in Data.Proxy.Singletons

type (a2 :: Proxy (a1 ~> b)) <*> (a3 :: Proxy a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Proxy a) (arg2 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Proxy a) (arg2 :: Proxy b)
type (arg :: Proxy a) *> (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) *> (arg1 :: Proxy b)
type (arg :: Proxy a) <* (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) <* (arg1 :: Proxy b)
PFunctor (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1) 
Instance details

Defined in Data.Proxy.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1)
type (arg :: a) <$ (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: a) <$ (arg1 :: Proxy b)
PMonad (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type (a2 :: Proxy a1) >>= (a3 :: a1 ~> Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (a2 :: Proxy a1) >>= (a3 :: a1 ~> Proxy b)
type (arg :: Proxy a) >> (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) >> (arg1 :: Proxy b)
type Return (arg :: a) 
Instance details

Defined in Data.Proxy.Singletons

type Return (arg :: a)
PMonadPlus (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Mzero 
Instance details

Defined in Data.Proxy.Singletons

type Mzero
type Mplus (arg :: Proxy a) (arg1 :: Proxy a) 
Instance details

Defined in Data.Proxy.Singletons

type Mplus (arg :: Proxy a) (arg1 :: Proxy a)
SAlternative (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sEmpty :: Sing (Empty :: Proxy a) Source #

(%<|>) :: forall a (t1 :: Proxy a) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (t1 <|> t2) Source #

SApplicative (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Proxy a) Source #

(%<*>) :: forall a b (t1 :: Proxy (a ~> b)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Proxy a) (t3 :: Proxy b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SFunctor (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SMonad (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

(%>>=) :: forall a b (t1 :: Proxy a) (t2 :: a ~> Proxy b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Proxy a) Source #

SMonadPlus (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sMzero :: Sing (Mzero :: Proxy a) Source #

sMplus :: forall a (t1 :: Proxy a) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Mplus t1 t2) Source #

PMonadZip (Proxy :: Type -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Associated Types

type Mzip (arg1 :: Proxy a) (arg2 :: Proxy b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Proxy a) (arg2 :: Proxy b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Proxy a1) (a4 :: Proxy b) 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Proxy a1) (a4 :: Proxy b)
type Munzip (arg :: Proxy (a, b)) 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: Proxy (a, b))
SMonadZip (Proxy :: Type -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sMzip :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Mzip t1 t2) Source #

sMzipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Proxy a) (t3 :: Proxy b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (MzipWith t1 t2 t3) Source #

sMunzip :: forall a b (t :: Proxy (a, b)). Sing t -> Sing (Munzip t) Source #

PFoldable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (a :: Proxy m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (a :: Proxy m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Proxy a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Proxy a1)
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Proxy a)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Proxy a1)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a)
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1)
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1)
type ToList (arg :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (arg :: Proxy a)
type Null (a2 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Proxy a1)
type Length (a2 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Proxy a1)
type Elem (a2 :: a1) (a3 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a2 :: a1) (a3 :: Proxy a1)
type Maximum (arg :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (arg :: Proxy a)
type Minimum (arg :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (arg :: Proxy a)
type Sum (a2 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a2 :: Proxy a1)
type Product (a2 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a2 :: Proxy a1)
SFoldable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Proxy m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Proxy a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Proxy a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Proxy a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Proxy a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Proxy a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Product t1) Source #

PTraversable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Proxy a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Proxy a1)
type SequenceA (a2 :: Proxy (f a1)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (a2 :: Proxy (f a1))
type MapM (a2 :: a1 ~> m b) (a3 :: Proxy a1) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (a2 :: a1 ~> m b) (a3 :: Proxy a1)
type Sequence (a2 :: Proxy (m a1)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (a2 :: Proxy (m a1))
STraversable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Proxy a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Proxy (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Proxy a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Proxy (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

NFData (Proxy a) #

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

Monoid (Proxy s) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Semigroup (Proxy s) #

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Bounded (Proxy t) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Generic (Proxy t) # 
Instance details

Defined in GHC.Internal.Generics

Associated Types

type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Ix (Proxy s) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int #

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int #

Read (Proxy t) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Show (Proxy s) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Eq (Proxy s) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s) #

Since: base-4.7.0.0

Instance details

Defined in GHC.Internal.Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Hashable (Proxy a) # 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

SingKind (Proxy t) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Demote (Proxy t) 
Instance details

Defined in Data.Proxy.Singletons

type Demote (Proxy t) = Proxy t

Methods

fromSing :: forall (a :: Proxy t). Sing a -> Demote (Proxy t) #

toSing :: Demote (Proxy t) -> SomeSing (Proxy t) #

SDecide (Proxy t) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

(%~) :: forall (a :: Proxy t) (b :: Proxy t). Sing a -> Sing b -> Decision (a :~: b) #

PEq (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

SEq (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

(%==) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

PMonoid (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Proxy.Singletons

type Mempty
SMonoid (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sMempty :: Sing (Mempty :: Proxy s) Source #

sMappend :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Proxy s]). Sing t -> Sing (Mconcat t) Source #

POrd (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

SOrd (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sCompare :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

PSemigroup (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

SSemigroup (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

(%<>) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Proxy s)). Sing t -> Sing (Sconcat t) Source #

PBounded (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type MinBound 
Instance details

Defined in Data.Proxy.Singletons

type MaxBound 
Instance details

Defined in Data.Proxy.Singletons

PEnum (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

SBounded (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

SEnum (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sSucc :: forall (t :: Proxy s). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Proxy s). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Proxy s) Source #

sFromEnum :: forall (t :: Proxy s). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Proxy s) (t2 :: Proxy s) (t3 :: Proxy s). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

PShow (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

SShow (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Proxy s) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Proxy s). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Proxy s]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

TestCoercion (SProxy :: Proxy t -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

testCoercion :: forall (a :: Proxy t) (b :: Proxy t). SProxy a -> SProxy b -> Maybe (Coercion a b) #

TestEquality (SProxy :: Proxy t -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

testEquality :: forall (a :: Proxy t) (b :: Proxy t). SProxy a -> SProxy b -> Maybe (a :~: b) #

SingI ('Proxy :: Proxy t) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sing :: Sing ('Proxy :: Proxy t) #

type MapM (a2 :: a1 ~> m b) (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Traversable.Singletons

type MapM (a2 :: a1 ~> m b) (a3 :: Proxy a1)
type Traverse (a2 :: a1 ~> f b) (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Proxy a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Proxy a) (arg2 :: Proxy b) Source # 
Instance details

Defined in Data.Proxy.Singletons

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Proxy a) (arg2 :: Proxy b)
type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Proxy a1) (a4 :: Proxy b) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type MzipWith (a2 :: a1 ~> (b ~> c)) (a3 :: Proxy a1) (a4 :: Proxy b)
type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1)
type FoldMap (a2 :: a1 ~> m) (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Proxy a1)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Proxy a1)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Proxy a1)
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Proxy a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Proxy a)
type Rep1 (Proxy :: k -> Type) #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
type Pure (a2 :: a1) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Pure (a2 :: a1)
type Return (arg :: a) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Return (arg :: a)
type Elem (a2 :: a1) (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a2 :: a1) (a3 :: Proxy a1)
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1)
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1)
type (arg :: a) <$ (arg1 :: Proxy b) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: a) <$ (arg1 :: Proxy b)
type Empty Source # 
Instance details

Defined in Data.Proxy.Singletons

type Empty
type Mzero Source # 
Instance details

Defined in Data.Proxy.Singletons

type Mzero
type Fold (a :: Proxy m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Fold (a :: Proxy m)
type Length (a2 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Proxy a1)
type Maximum (arg :: Proxy a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (arg :: Proxy a)
type Minimum (arg :: Proxy a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (arg :: Proxy a)
type Null (a2 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Proxy a1)
type Product (a2 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Product (a2 :: Proxy a1)
type Sum (a2 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a2 :: Proxy a1)
type ToList (arg :: Proxy a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type ToList (arg :: Proxy a)
type (a2 :: Proxy a1) <|> (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (a2 :: Proxy a1) <|> (a3 :: Proxy a1)
type Mplus (arg :: Proxy a) (arg1 :: Proxy a) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Mplus (arg :: Proxy a) (arg1 :: Proxy a)
type Munzip (arg :: Proxy (a, b)) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Munzip (arg :: Proxy (a, b))
type Sequence (a2 :: Proxy (m a1)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (a2 :: Proxy (m a1))
type SequenceA (a2 :: Proxy (f a1)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (a2 :: Proxy (f a1))
type (arg :: Proxy a) *> (arg1 :: Proxy b) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) *> (arg1 :: Proxy b)
type (arg :: Proxy a) <* (arg1 :: Proxy b) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) <* (arg1 :: Proxy b)
type (a2 :: Proxy (a1 ~> b)) <*> (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (a2 :: Proxy (a1 ~> b)) <*> (a3 :: Proxy a1)
type (arg :: Proxy a) >> (arg1 :: Proxy b) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) >> (arg1 :: Proxy b)
type (a2 :: Proxy a1) >>= (a3 :: a1 ~> Proxy b) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (a2 :: Proxy a1) >>= (a3 :: a1 ~> Proxy b)
type Mzip (arg1 :: Proxy a) (arg2 :: Proxy b) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Mzip (arg1 :: Proxy a) (arg2 :: Proxy b)
type Rep (Proxy t) #

Since: base-4.6.0.0

Instance details

Defined in GHC.Internal.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "GHC.Internal.Data.Proxy" "ghc-internal" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: Type -> Type))
type Demote (Proxy t) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Demote (Proxy t) = Proxy t
type Sing Source # 
Instance details

Defined in Data.Proxy.Singletons

type Sing = SProxy :: Proxy t -> Type
type Mempty Source # 
Instance details

Defined in Data.Proxy.Singletons

type Mempty
type MaxBound Source # 
Instance details

Defined in Data.Proxy.Singletons

type MinBound Source # 
Instance details

Defined in Data.Proxy.Singletons

type Mconcat (a :: [Proxy s]) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Mconcat (a :: [Proxy s])
type Sconcat (a :: NonEmpty (Proxy s)) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Sconcat (a :: NonEmpty (Proxy s))
type FromEnum (a :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type FromEnum (a :: Proxy s)
type Pred (a :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Pred (a :: Proxy s)
type Succ (a :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Succ (a :: Proxy s)
type ToEnum a Source # 
Instance details

Defined in Data.Proxy.Singletons

type ToEnum a
type Show_ (arg :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Show_ (arg :: Proxy s)
type (arg :: Proxy s) /= (arg1 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy s) /= (arg1 :: Proxy s)
type (a1 :: Proxy s) == (a2 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (a1 :: Proxy s) == (a2 :: Proxy s)
type Mappend (arg :: Proxy s) (arg1 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Mappend (arg :: Proxy s) (arg1 :: Proxy s)
type (arg :: Proxy s) < (arg1 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy s) < (arg1 :: Proxy s)
type (arg :: Proxy s) <= (arg1 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy s) <= (arg1 :: Proxy s)
type (arg :: Proxy s) > (arg1 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy s) > (arg1 :: Proxy s)
type (arg :: Proxy s) >= (arg1 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy s) >= (arg1 :: Proxy s)
type Compare (a1 :: Proxy s) (a2 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Compare (a1 :: Proxy s) (a2 :: Proxy s)
type Max (arg :: Proxy s) (arg1 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Max (arg :: Proxy s) (arg1 :: Proxy s)
type Min (arg :: Proxy s) (arg1 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Min (arg :: Proxy s) (arg1 :: Proxy s)
type (a1 :: Proxy s) <> (a2 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type (a1 :: Proxy s) <> (a2 :: Proxy s)
type EnumFromTo (a1 :: Proxy s) (a2 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type EnumFromTo (a1 :: Proxy s) (a2 :: Proxy s)
type ShowList (arg :: [Proxy s]) arg1 Source # 
Instance details

Defined in Data.Proxy.Singletons

type ShowList (arg :: [Proxy s]) arg1
type EnumFromThenTo (a1 :: Proxy s) (a2 :: Proxy s) (a3 :: Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

type EnumFromThenTo (a1 :: Proxy s) (a2 :: Proxy s) (a3 :: Proxy s)
type ShowsPrec a1 (a2 :: Proxy s) a3 Source # 
Instance details

Defined in Data.Proxy.Singletons

type ShowsPrec a1 (a2 :: Proxy s) a3

type (@@) (a :: k1 ~> k2) (b :: k1) = Apply a b #

data (@@@#@$) (a1 :: TyFun (a ~> b) (a ~> b)) #

Instances

Instances details
type Apply ((@@@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) # 
Instance details

Defined in Data.Singletons

type Apply ((@@@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) = (@@@#@$$) f

data (a1 :: a ~> b) @@@#@$$ (b1 :: TyFun a b) #

Instances

Instances details
type Apply ((@@@#@$$) f :: TyFun k1 k2 -> Type) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply ((@@@#@$$) f :: TyFun k1 k2 -> Type) (x :: k1) = f @@ x

type (@@@#@$$$) (f :: a ~> b) (x :: a) = f @@ x #

type family Apply (f :: k1 ~> k2) (x :: k1) :: k2 #

Instances

Instances details
type Apply GetAllSym0 (a6989586621679458594 :: All) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply GetAllSym0 (a6989586621679458594 :: All) = GetAll a6989586621679458594
type Apply GetAnySym0 (a6989586621679458610 :: Any) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply GetAnySym0 (a6989586621679458610 :: Any) = GetAny a6989586621679458610
type Apply KnownNatSym0 (a6989586621679377837 :: Nat) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply KnownNatSym0 (a6989586621679377837 :: Nat) = KnownNat a6989586621679377837
type Apply Log2Sym0 (a6989586621679378480 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply Log2Sym0 (a6989586621679378480 :: Natural) = Log2 a6989586621679378480
type Apply NatToCharSym0 (a6989586621679382082 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply NatToCharSym0 (a6989586621679382082 :: Natural) = NatToChar a6989586621679382082
type Apply AllSym0 (a6989586621679458591 :: Bool) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply AllSym0 (a6989586621679458591 :: Bool) = 'All a6989586621679458591
type Apply AnySym0 (a6989586621679458607 :: Bool) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply AnySym0 (a6989586621679458607 :: Bool) = 'Any a6989586621679458607
type Apply NotSym0 (a6989586621679124212 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply NotSym0 (a6989586621679124212 :: Bool) = Not a6989586621679124212
type Apply CharToNatSym0 (a6989586621679381852 :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply CharToNatSym0 (a6989586621679381852 :: Char) = CharToNat a6989586621679381852
type Apply KnownCharSym0 (a6989586621679377841 :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply KnownCharSym0 (a6989586621679377841 :: Char) = KnownChar a6989586621679377841
type Apply KnownSymbolSym0 (a6989586621679377839 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply KnownSymbolSym0 (a6989586621679377839 :: Symbol) = KnownSymbol a6989586621679377839
type Apply ShowCommaSpaceSym0 (a6989586621679807326 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCommaSpaceSym0 (a6989586621679807326 :: Symbol) = ShowCommaSpace a6989586621679807326
type Apply ShowSpaceSym0 (a6989586621679807332 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowSpaceSym0 (a6989586621679807332 :: Symbol) = ShowSpace a6989586621679807332
type Apply DemoteSym0 (x :: Type) # 
Instance details

Defined in Data.Singletons

type Apply DemoteSym0 (x :: Type) = Demote x
type Apply (AbsurdSym0 :: TyFun Void a -> Type) (a6989586621679152715 :: Void) Source # 
Instance details

Defined in Data.Void.Singletons

type Apply (AbsurdSym0 :: TyFun Void a -> Type) (a6989586621679152715 :: Void) = Absurd a6989586621679152715 :: a
type Apply (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) (a6989586621679803716 :: PErrorMessage) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) (a6989586621679803716 :: PErrorMessage) = TypeError a6989586621679803716 :: a
type Apply (DivSym1 a6989586621679378709 :: TyFun Natural Natural -> Type) (a6989586621679378710 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (DivSym1 a6989586621679378709 :: TyFun Natural Natural -> Type) (a6989586621679378710 :: Natural) = Div a6989586621679378709 a6989586621679378710
type Apply (ModSym1 a6989586621679379154 :: TyFun Natural Natural -> Type) (a6989586621679379155 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (ModSym1 a6989586621679379154 :: TyFun Natural Natural -> Type) (a6989586621679379155 :: Natural) = Mod a6989586621679379154 a6989586621679379155
type Apply (QuotSym1 a6989586621679379824 :: TyFun Natural Natural -> Type) (a6989586621679379825 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (QuotSym1 a6989586621679379824 :: TyFun Natural Natural -> Type) (a6989586621679379825 :: Natural) = Quot a6989586621679379824 a6989586621679379825
type Apply (RemSym1 a6989586621679379813 :: TyFun Natural Natural -> Type) (a6989586621679379814 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (RemSym1 a6989586621679379813 :: TyFun Natural Natural -> Type) (a6989586621679379814 :: Natural) = Rem a6989586621679379813 a6989586621679379814
type Apply ((^@#@$$) a6989586621679369666 :: TyFun Natural Natural -> Type) (a6989586621679369667 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((^@#@$$) a6989586621679369666 :: TyFun Natural Natural -> Type) (a6989586621679369667 :: Natural) = a6989586621679369666 ^ a6989586621679369667
type Apply (ToEnumSym0 :: TyFun Natural a -> Type) (a6989586621679414060 :: Natural) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (ToEnumSym0 :: TyFun Natural a -> Type) (a6989586621679414060 :: Natural) = ToEnum a6989586621679414060 :: a
type Apply (FromIntegerSym0 :: TyFun Natural a -> Type) (a6989586621679398591 :: Natural) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (FromIntegerSym0 :: TyFun Natural a -> Type) (a6989586621679398591 :: Natural) = FromInteger a6989586621679398591 :: a
type Apply ((&&@#@$$) a6989586621679123502 :: TyFun Bool Bool -> Type) (a6989586621679123503 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((&&@#@$$) a6989586621679123502 :: TyFun Bool Bool -> Type) (a6989586621679123503 :: Bool) = a6989586621679123502 && a6989586621679123503
type Apply ((||@#@$$) a6989586621679123865 :: TyFun Bool Bool -> Type) (a6989586621679123866 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((||@#@$$) a6989586621679123865 :: TyFun Bool Bool -> Type) (a6989586621679123866 :: Bool) = a6989586621679123865 || a6989586621679123866
type Apply (ConsSymbolSym1 a6989586621679381116 :: TyFun Symbol Symbol -> Type) (a6989586621679381117 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (ConsSymbolSym1 a6989586621679381116 :: TyFun Symbol Symbol -> Type) (a6989586621679381117 :: Symbol) = ConsSymbol a6989586621679381116 a6989586621679381117
type Apply (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) (a6989586621679807376 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) (a6989586621679807376 :: Symbol) = ShowChar a6989586621679807375 a6989586621679807376
type Apply (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) (a6989586621679807365 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) (a6989586621679807365 :: Symbol) = ShowString a6989586621679807364 a6989586621679807365
type Apply (FromStringSym0 :: TyFun Symbol a -> Type) (a6989586621680338575 :: Symbol) Source # 
Instance details

Defined in Data.String.Singletons

type Apply (FromStringSym0 :: TyFun Symbol a -> Type) (a6989586621680338575 :: Symbol) = FromString a6989586621680338575 :: a
type Apply (ErrorSym0 :: TyFun Symbol a -> Type) (a6989586621679368947 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorSym0 :: TyFun Symbol a -> Type) (a6989586621679368947 :: Symbol) = Error a6989586621679368947 :: a
type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) (a6989586621679369227 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) (a6989586621679369227 :: Symbol) = ErrorWithoutStackTrace a6989586621679369227 :: a
type Apply ((~>@#@$$) x :: TyFun Type Type -> Type) (y :: Type) # 
Instance details

Defined in Data.Singletons

type Apply ((~>@#@$$) x :: TyFun Type Type -> Type) (y :: Type) = x ~> y
type Apply (FromEnumSym0 :: TyFun a Natural -> Type) (a6989586621679414063 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (FromEnumSym0 :: TyFun a Natural -> Type) (a6989586621679414063 :: a) = FromEnum a6989586621679414063
type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621679807414 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621679807414 :: a) = Show_ a6989586621679807414
type Apply (PredSym0 :: TyFun a a -> Type) (a6989586621679414057 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (PredSym0 :: TyFun a a -> Type) (a6989586621679414057 :: a) = Pred a6989586621679414057
type Apply (SuccSym0 :: TyFun a a -> Type) (a6989586621679414054 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (SuccSym0 :: TyFun a a -> Type) (a6989586621679414054 :: a) = Succ a6989586621679414054
type Apply (IdSym0 :: TyFun a a -> Type) (a6989586621679154359 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (IdSym0 :: TyFun a a -> Type) (a6989586621679154359 :: a) = Id a6989586621679154359
type Apply (AbsSym0 :: TyFun a a -> Type) (a6989586621679398585 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (AbsSym0 :: TyFun a a -> Type) (a6989586621679398585 :: a) = Abs a6989586621679398585
type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679398582 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679398582 :: a) = Negate a6989586621679398582
type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679398588 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679398588 :: a) = Signum a6989586621679398588
type Apply (KindOfSym0 :: TyFun k Type -> Type) (x :: k) # 
Instance details

Defined in Data.Singletons

type Apply (KindOfSym0 :: TyFun k Type -> Type) (x :: k) = KindOf x
type Apply ((!!@#@$$) a6989586621680286938 :: TyFun Natural a -> Type) (a6989586621680286939 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$$) a6989586621680286938 :: TyFun Natural a -> Type) (a6989586621680286939 :: Natural) = a6989586621680286938 !! a6989586621680286939
type Apply ((!!@#@$$) a6989586621679544266 :: TyFun Natural a -> Type) (a6989586621679544267 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$$) a6989586621679544266 :: TyFun Natural a -> Type) (a6989586621679544267 :: Natural) = a6989586621679544266 !! a6989586621679544267
type Apply (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) (a6989586621679807419 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) (a6989586621679807419 :: Symbol) = ShowList a6989586621679807418 a6989586621679807419
type Apply (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) (a6989586621679807348 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) (a6989586621679807348 :: Symbol) = ShowParen a6989586621679807346 a6989586621679807347 a6989586621679807348
type Apply (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) (a6989586621679807402 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) (a6989586621679807402 :: Symbol) = Shows a6989586621679807401 a6989586621679807402
type Apply (CompareSym1 a6989586621679189966 :: TyFun a Ordering -> Type) (a6989586621679189967 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym1 a6989586621679189966 :: TyFun a Ordering -> Type) (a6989586621679189967 :: a) = Compare a6989586621679189966 a6989586621679189967
type Apply ((/=@#@$$) a6989586621679128030 :: TyFun a Bool -> Type) (a6989586621679128031 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$$) a6989586621679128030 :: TyFun a Bool -> Type) (a6989586621679128031 :: a) = a6989586621679128030 /= a6989586621679128031
type Apply ((==@#@$$) a6989586621679128025 :: TyFun a Bool -> Type) (a6989586621679128026 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$$) a6989586621679128025 :: TyFun a Bool -> Type) (a6989586621679128026 :: a) = a6989586621679128025 == a6989586621679128026
type Apply ((<=@#@$$) a6989586621679189976 :: TyFun a Bool -> Type) (a6989586621679189977 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$$) a6989586621679189976 :: TyFun a Bool -> Type) (a6989586621679189977 :: a) = a6989586621679189976 <= a6989586621679189977
type Apply ((<@#@$$) a6989586621679189971 :: TyFun a Bool -> Type) (a6989586621679189972 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$$) a6989586621679189971 :: TyFun a Bool -> Type) (a6989586621679189972 :: a) = a6989586621679189971 < a6989586621679189972
type Apply ((>=@#@$$) a6989586621679189986 :: TyFun a Bool -> Type) (a6989586621679189987 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$$) a6989586621679189986 :: TyFun a Bool -> Type) (a6989586621679189987 :: a) = a6989586621679189986 >= a6989586621679189987
type Apply ((>@#@$$) a6989586621679189981 :: TyFun a Bool -> Type) (a6989586621679189982 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$$) a6989586621679189981 :: TyFun a Bool -> Type) (a6989586621679189982 :: a) = a6989586621679189981 > a6989586621679189982
type Apply (MappendSym1 a6989586621679860746 :: TyFun a a -> Type) (a6989586621679860747 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym1 a6989586621679860746 :: TyFun a a -> Type) (a6989586621679860747 :: a) = Mappend a6989586621679860746 a6989586621679860747
type Apply (MaxSym1 a6989586621679189991 :: TyFun a a -> Type) (a6989586621679189992 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym1 a6989586621679189991 :: TyFun a a -> Type) (a6989586621679189992 :: a) = Max a6989586621679189991 a6989586621679189992
type Apply (MinSym1 a6989586621679189996 :: TyFun a a -> Type) (a6989586621679189997 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym1 a6989586621679189996 :: TyFun a a -> Type) (a6989586621679189997 :: a) = Min a6989586621679189996 a6989586621679189997
type Apply ((<>@#@$$) a6989586621679173979 :: TyFun a a -> Type) (a6989586621679173980 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$$) a6989586621679173979 :: TyFun a a -> Type) (a6989586621679173980 :: a) = a6989586621679173979 <> a6989586621679173980
type Apply (AsTypeOfSym1 a6989586621679154319 :: TyFun a a -> Type) (a6989586621679154320 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym1 a6989586621679154319 :: TyFun a a -> Type) (a6989586621679154320 :: a) = AsTypeOf a6989586621679154319 a6989586621679154320
type Apply ((*@#@$$) a6989586621679398578 :: TyFun a a -> Type) (a6989586621679398579 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$$) a6989586621679398578 :: TyFun a a -> Type) (a6989586621679398579 :: a) = a6989586621679398578 * a6989586621679398579
type Apply ((+@#@$$) a6989586621679398568 :: TyFun a a -> Type) (a6989586621679398569 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$$) a6989586621679398568 :: TyFun a a -> Type) (a6989586621679398569 :: a) = a6989586621679398568 + a6989586621679398569
type Apply ((-@#@$$) a6989586621679398573 :: TyFun a a -> Type) (a6989586621679398574 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$$) a6989586621679398573 :: TyFun a a -> Type) (a6989586621679398574 :: a) = a6989586621679398573 - a6989586621679398574
type Apply (SubtractSym1 a6989586621679398561 :: TyFun a a -> Type) (a6989586621679398562 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym1 a6989586621679398561 :: TyFun a a -> Type) (a6989586621679398562 :: a) = Subtract a6989586621679398561 a6989586621679398562
type Apply (DefaultEqSym1 a6989586621679129674 :: TyFun k Bool -> Type) (a6989586621679129675 :: k) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply (DefaultEqSym1 a6989586621679129674 :: TyFun k Bool -> Type) (a6989586621679129675 :: k) = DefaultEq a6989586621679129674 a6989586621679129675
type Apply ((<=?@#@$$) a6989586621679370104 :: TyFun k Bool -> Type) (a6989586621679370105 :: k) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((<=?@#@$$) a6989586621679370104 :: TyFun k Bool -> Type) (a6989586621679370105 :: k) = a6989586621679370104 <=? a6989586621679370105
type Apply (SameKindSym1 x :: TyFun k Constraint -> Type) (y :: k) # 
Instance details

Defined in Data.Singletons

type Apply (SameKindSym1 x :: TyFun k Constraint -> Type) (y :: k) = SameKind x y
type Apply (Bool_Sym2 a6989586621679122246 a6989586621679122247 :: TyFun Bool a -> Type) (a6989586621679122248 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym2 a6989586621679122246 a6989586621679122247 :: TyFun Bool a -> Type) (a6989586621679122248 :: Bool) = Bool_ a6989586621679122246 a6989586621679122247 a6989586621679122248
type Apply (ShowListWithSym2 a6989586621679807383 a6989586621679807384 :: TyFun Symbol Symbol -> Type) (a6989586621679807385 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym2 a6989586621679807383 a6989586621679807384 :: TyFun Symbol Symbol -> Type) (a6989586621679807385 :: Symbol) = ShowListWith a6989586621679807383 a6989586621679807384 a6989586621679807385
type Apply (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) (a6989586621679807411 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) (a6989586621679807411 :: Symbol) = ShowsPrec a6989586621679807409 a6989586621679807410 a6989586621679807411
type Apply (UntilSym2 a6989586621679154281 a6989586621679154282 :: TyFun a a -> Type) (a6989586621679154283 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym2 a6989586621679154281 a6989586621679154282 :: TyFun a a -> Type) (a6989586621679154283 :: a) = Until a6989586621679154281 a6989586621679154282 a6989586621679154283
type Apply (($!@#@$$) a6989586621679154299 :: TyFun a b -> Type) (a6989586621679154300 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$$) a6989586621679154299 :: TyFun a b -> Type) (a6989586621679154300 :: a) = a6989586621679154299 $! a6989586621679154300
type Apply (($@#@$$) a6989586621679154308 :: TyFun a b -> Type) (a6989586621679154309 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$$) a6989586621679154308 :: TyFun a b -> Type) (a6989586621679154309 :: a) = a6989586621679154308 $ a6989586621679154309
type Apply (ConstSym1 a6989586621679154354 :: TyFun b a -> Type) (a6989586621679154355 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym1 a6989586621679154354 :: TyFun b a -> Type) (a6989586621679154355 :: b) = Const a6989586621679154354 a6989586621679154355
type Apply (SeqSym1 a6989586621679154272 :: TyFun b b -> Type) (a6989586621679154273 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym1 a6989586621679154272 :: TyFun b b -> Type) (a6989586621679154273 :: b) = Seq a6989586621679154272 a6989586621679154273
type Apply (IfSym2 a6989586621679124436 a6989586621679124437 :: TyFun k k -> Type) (a6989586621679124438 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym2 a6989586621679124436 a6989586621679124437 :: TyFun k k -> Type) (a6989586621679124438 :: k) = If a6989586621679124436 a6989586621679124437 a6989586621679124438
type Apply ((@@@#@$$) f :: TyFun k1 k2 -> Type) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply ((@@@#@$$) f :: TyFun k1 k2 -> Type) (x :: k1) = f @@ x
type Apply (ApplySym1 f :: TyFun k1 k2 -> Type) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply (ApplySym1 f :: TyFun k1 k2 -> Type) (x :: k1) = Apply f x
type Apply (ApplyTyConAux1 f :: TyFun k1 k2 -> Type) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply (ApplyTyConAux1 f :: TyFun k1 k2 -> Type) (x :: k1) = f x
type Apply (ComparingSym2 a6989586621679189957 a6989586621679189958 :: TyFun b Ordering -> Type) (a6989586621679189959 :: b) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym2 a6989586621679189957 a6989586621679189958 :: TyFun b Ordering -> Type) (a6989586621679189959 :: b) = Comparing a6989586621679189957 a6989586621679189958 a6989586621679189959
type Apply (TyCon f :: k1 ~> k3) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply (TyCon f :: k1 ~> k3) (x :: k1) = ApplyTyCon f @@ x
type Apply (a6989586621679154339 .@#@$$$ a6989586621679154340 :: TyFun a c -> Type) (a6989586621679154341 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (a6989586621679154339 .@#@$$$ a6989586621679154340 :: TyFun a c -> Type) (a6989586621679154341 :: a) = (a6989586621679154339 . a6989586621679154340) a6989586621679154341
type Apply (FlipSym2 a6989586621679154327 a6989586621679154328 :: TyFun a c -> Type) (a6989586621679154329 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym2 a6989586621679154327 a6989586621679154328 :: TyFun a c -> Type) (a6989586621679154329 :: a) = Flip a6989586621679154327 a6989586621679154328 a6989586621679154329
type Apply (CurrySym2 a6989586621679147661 a6989586621679147662 :: TyFun b c -> Type) (a6989586621679147663 :: b) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym2 a6989586621679147661 a6989586621679147662 :: TyFun b c -> Type) (a6989586621679147663 :: b) = Curry a6989586621679147661 a6989586621679147662 a6989586621679147663
type Apply (ApplyTyConAux2 f :: TyFun k4 k7 -> Type) (x :: k4) # 
Instance details

Defined in Data.Singletons

type Apply (ApplyTyConAux2 f :: TyFun k4 k7 -> Type) (x :: k4) = TyCon (f x)
type Apply (OnSym3 a6989586621679253973 a6989586621679253974 a6989586621679253975 :: TyFun a c -> Type) (a6989586621679253976 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym3 a6989586621679253973 a6989586621679253974 a6989586621679253975 :: TyFun a c -> Type) (a6989586621679253976 :: a) = On a6989586621679253973 a6989586621679253974 a6989586621679253975 a6989586621679253976
type Apply UnconsSymbolSym0 (a6989586621679381627 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply UnconsSymbolSym0 (a6989586621679381627 :: Symbol) = UnconsSymbol a6989586621679381627
type Apply (GuardSym0 :: TyFun Bool (f ()) -> Type) (a6989586621679270986 :: Bool) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (GuardSym0 :: TyFun Bool (f ()) -> Type) (a6989586621679270986 :: Bool) = Guard a6989586621679270986 :: f ()
type Apply (FirstSym0 :: TyFun a (First a) -> Type) (a6989586621679458702 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (FirstSym0 :: TyFun a (First a) -> Type) (a6989586621679458702 :: a) = 'First a6989586621679458702
type Apply (LastSym0 :: TyFun a (Last a) -> Type) (a6989586621679458721 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (LastSym0 :: TyFun a (Last a) -> Type) (a6989586621679458721 :: a) = 'Last a6989586621679458721
type Apply (MaxSym0 :: TyFun a (Max a) -> Type) (a6989586621679458683 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (MaxSym0 :: TyFun a (Max a) -> Type) (a6989586621679458683 :: a) = 'Max a6989586621679458683
type Apply (MinSym0 :: TyFun a (Min a) -> Type) (a6989586621679458664 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (MinSym0 :: TyFun a (Min a) -> Type) (a6989586621679458664 :: a) = 'Min a6989586621679458664
type Apply (IdentitySym0 :: TyFun a (Identity a) -> Type) (a6989586621679051204 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (IdentitySym0 :: TyFun a (Identity a) -> Type) (a6989586621679051204 :: a) = 'Identity a6989586621679051204
type Apply (DownSym0 :: TyFun a (Down a) -> Type) (a6989586621679198735 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (DownSym0 :: TyFun a (Down a) -> Type) (a6989586621679198735 :: a) = 'Down a6989586621679198735
type Apply (DualSym0 :: TyFun a (Dual a) -> Type) (a6989586621679458575 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (DualSym0 :: TyFun a (Dual a) -> Type) (a6989586621679458575 :: a) = 'Dual a6989586621679458575
type Apply (ProductSym0 :: TyFun a (Product a) -> Type) (a6989586621679458645 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (ProductSym0 :: TyFun a (Product a) -> Type) (a6989586621679458645 :: a) = 'Product a6989586621679458645
type Apply (SumSym0 :: TyFun a (Sum a) -> Type) (a6989586621679458626 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (SumSym0 :: TyFun a (Sum a) -> Type) (a6989586621679458626 :: a) = 'Sum a6989586621679458626
type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679050265 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679050265 :: a) = 'Just a6989586621679050265
type Apply (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) (a6989586621679458740 :: m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) (a6989586621679458740 :: m) = 'WrapMonoid a6989586621679458740
type Apply (TextSym0 :: TyFun s (ErrorMessage' s) -> Type) (a6989586621679803706 :: s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply (TextSym0 :: TyFun s (ErrorMessage' s) -> Type) (a6989586621679803706 :: s) = 'Text a6989586621679803706
type Apply (ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type) (a6989586621679544287 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type) (a6989586621679544287 :: a) = Replicate a6989586621679544286 a6989586621679544287
type Apply (EnumFromToSym1 a6989586621679414067 :: TyFun a [a] -> Type) (a6989586621679414068 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym1 a6989586621679414067 :: TyFun a [a] -> Type) (a6989586621679414068 :: a) = EnumFromTo a6989586621679414067 a6989586621679414068
type Apply (PureSym0 :: TyFun a (f a) -> Type) (a6989586621679271251 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (PureSym0 :: TyFun a (f a) -> Type) (a6989586621679271251 :: a) = Pure a6989586621679271251 :: f a
type Apply (ReturnSym0 :: TyFun a (m a) -> Type) (a6989586621679271344 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ReturnSym0 :: TyFun a (m a) -> Type) (a6989586621679271344 :: a) = Return a6989586621679271344 :: m a
type Apply (ShowTypeSym0 :: TyFun t (ErrorMessage' s) -> Type) (a6989586621679803708 :: t) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply (ShowTypeSym0 :: TyFun t (ErrorMessage' s) -> Type) (a6989586621679803708 :: t) = 'ShowType a6989586621679803708 :: ErrorMessage' s
type Apply (UnfoldSym1 a6989586621680287356 :: TyFun a (NonEmpty b) -> Type) (a6989586621680287357 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym1 a6989586621680287356 :: TyFun a (NonEmpty b) -> Type) (a6989586621680287357 :: a) = Unfold a6989586621680287356 a6989586621680287357
type Apply (UnfoldrSym1 a6989586621680287321 :: TyFun a (NonEmpty b) -> Type) (a6989586621680287322 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym1 a6989586621680287321 :: TyFun a (NonEmpty b) -> Type) (a6989586621680287322 :: a) = Unfoldr a6989586621680287321 a6989586621680287322
type Apply (EnumFromThenToSym2 a6989586621679414073 a6989586621679414074 :: TyFun a [a] -> Type) (a6989586621679414075 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym2 a6989586621679414073 a6989586621679414074 :: TyFun a [a] -> Type) (a6989586621679414075 :: a) = EnumFromThenTo a6989586621679414073 a6989586621679414074 a6989586621679414075
type Apply (UnfoldrSym1 a6989586621679545055 :: TyFun b [a] -> Type) (a6989586621679545056 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnfoldrSym1 a6989586621679545055 :: TyFun b [a] -> Type) (a6989586621679545056 :: b) = Unfoldr a6989586621679545055 a6989586621679545056
type Apply (($>@#@$$) a6989586621679357502 :: TyFun b (f b) -> Type) (a6989586621679357503 :: b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$$) a6989586621679357502 :: TyFun b (f b) -> Type) (a6989586621679357503 :: b) = a6989586621679357502 $> a6989586621679357503
type Apply (a6989586621680354976 <=<@#@$$$ a6989586621680354977 :: TyFun a (m c) -> Type) (a6989586621680354978 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (a6989586621680354976 <=<@#@$$$ a6989586621680354977 :: TyFun a (m c) -> Type) (a6989586621680354978 :: a) = (a6989586621680354976 <=< a6989586621680354977) a6989586621680354978
type Apply (a6989586621680354988 >=>@#@$$$ a6989586621680354989 :: TyFun a (m c) -> Type) (a6989586621680354990 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (a6989586621680354988 >=>@#@$$$ a6989586621680354989 :: TyFun a (m c) -> Type) (a6989586621680354990 :: a) = (a6989586621680354988 >=> a6989586621680354989) a6989586621680354990
type Apply DivSym0 (a6989586621679378709 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply DivSym0 (a6989586621679378709 :: Natural) = DivSym1 a6989586621679378709
type Apply ModSym0 (a6989586621679379154 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply ModSym0 (a6989586621679379154 :: Natural) = ModSym1 a6989586621679379154
type Apply QuotSym0 (a6989586621679379824 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply QuotSym0 (a6989586621679379824 :: Natural) = QuotSym1 a6989586621679379824
type Apply RemSym0 (a6989586621679379813 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply RemSym0 (a6989586621679379813 :: Natural) = RemSym1 a6989586621679379813
type Apply (^@#@$) (a6989586621679369666 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (^@#@$) (a6989586621679369666 :: Natural) = (^@#@$$) a6989586621679369666
type Apply DivModSym0 (a6989586621679379842 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply DivModSym0 (a6989586621679379842 :: Natural) = DivModSym1 a6989586621679379842
type Apply QuotRemSym0 (a6989586621679379835 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply QuotRemSym0 (a6989586621679379835 :: Natural) = QuotRemSym1 a6989586621679379835
type Apply ShowParenSym0 (a6989586621679807346 :: Bool) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowParenSym0 (a6989586621679807346 :: Bool) = ShowParenSym1 a6989586621679807346
type Apply (&&@#@$) (a6989586621679123502 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (&&@#@$) (a6989586621679123502 :: Bool) = (&&@#@$$) a6989586621679123502
type Apply (||@#@$) (a6989586621679123865 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (||@#@$) (a6989586621679123865 :: Bool) = (||@#@$$) a6989586621679123865
type Apply ConsSymbolSym0 (a6989586621679381116 :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply ConsSymbolSym0 (a6989586621679381116 :: Char) = ConsSymbolSym1 a6989586621679381116
type Apply ShowCharSym0 (a6989586621679807375 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621679807375 :: Char) = ShowCharSym1 a6989586621679807375
type Apply ShowStringSym0 (a6989586621679807364 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621679807364 :: Symbol) = ShowStringSym1 a6989586621679807364
type Apply (~>@#@$) (x :: Type) # 
Instance details

Defined in Data.Singletons

type Apply (~>@#@$) (x :: Type) = (~>@#@$$) x
type Apply (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287146 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287146 :: Natural) = SplitAtSym1 a6989586621680287146 :: TyFun (NonEmpty a) ([a], [a]) -> Type
type Apply (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287155 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287155 :: Natural) = DropSym1 a6989586621680287155 :: TyFun (NonEmpty a) [a] -> Type
type Apply (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287164 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287164 :: Natural) = TakeSym1 a6989586621680287164 :: TyFun (NonEmpty a) [a] -> Type
type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679544425 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679544425 :: Natural) = SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type
type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544432 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544432 :: Natural) = DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type
type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544445 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544445 :: Natural) = TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type
type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807409 :: Natural) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807409 :: Natural) = ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type
type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679544286 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679544286 :: Natural) = ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type
type Apply (DivModSym1 a6989586621679379842 :: TyFun Natural (Natural, Natural) -> Type) (a6989586621679379843 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (DivModSym1 a6989586621679379842 :: TyFun Natural (Natural, Natural) -> Type) (a6989586621679379843 :: Natural) = DivMod a6989586621679379842 a6989586621679379843
type Apply (QuotRemSym1 a6989586621679379835 :: TyFun Natural (Natural, Natural) -> Type) (a6989586621679379836 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (QuotRemSym1 a6989586621679379835 :: TyFun Natural (Natural, Natural) -> Type) (a6989586621679379836 :: Natural) = QuotRem a6989586621679379835 a6989586621679379836
type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621680354860 :: Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621680354860 :: Bool) = UnlessSym1 a6989586621680354860 :: TyFun (f ()) (f ()) -> Type
type Apply (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621679271164 :: Bool) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621679271164 :: Bool) = WhenSym1 a6989586621679271164 :: TyFun (f ()) (f ()) -> Type
type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679124436 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679124436 :: Bool) = IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type
type Apply ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287295 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287295 :: a) = (<|@#@$$) a6989586621680287295
type Apply (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287288 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287288 :: a) = ConsSym1 a6989586621680287288
type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287177 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287177 :: a) = IntersperseSym1 a6989586621680287177
type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679390214 :: a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679390214 :: a) = FromMaybeSym1 a6989586621679390214
type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621680287232 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621680287232 :: a) = InsertSym1 a6989586621680287232
type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679050362 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679050362 :: a) = (:|@#@$$) a6989586621679050362
type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679544658 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679544658 :: a) = ElemIndexSym1 a6989586621679544658
type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679544649 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679544649 :: a) = ElemIndicesSym1 a6989586621679544649
type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544803 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544803 :: a) = DeleteSym1 a6989586621679544803
type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544400 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544400 :: a) = InsertSym1 a6989586621679544400
type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679545422 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679545422 :: a) = IntersperseSym1 a6989586621679545422
type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679050289 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679050289 :: a) = (:@#@$$) a6989586621679050289
type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807401 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807401 :: a) = ShowsSym1 a6989586621679807401
type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679189966 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679189966 :: a) = CompareSym1 a6989586621679189966
type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679122246 :: a) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679122246 :: a) = Bool_Sym1 a6989586621679122246
type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679414073 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679414073 :: a) = EnumFromThenToSym1 a6989586621679414073
type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128030 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128030 :: a) = (/=@#@$$) a6989586621679128030
type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128025 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128025 :: a) = (==@#@$$) a6989586621679128025
type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189976 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189976 :: a) = (<=@#@$$) a6989586621679189976
type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189971 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189971 :: a) = (<@#@$$) a6989586621679189971
type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189986 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189986 :: a) = (>=@#@$$) a6989586621679189986
type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189981 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189981 :: a) = (>@#@$$) a6989586621679189981
type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414067 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414067 :: a) = EnumFromToSym1 a6989586621679414067
type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679860746 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679860746 :: a) = MappendSym1 a6989586621679860746
type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189991 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189991 :: a) = MaxSym1 a6989586621679189991
type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189996 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189996 :: a) = MinSym1 a6989586621679189996
type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679173979 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679173979 :: a) = (<>@#@$$) a6989586621679173979
type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679154319 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679154319 :: a) = AsTypeOfSym1 a6989586621679154319
type Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398578 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398578 :: a) = (*@#@$$) a6989586621679398578
type Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398568 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398568 :: a) = (+@#@$$) a6989586621679398568
type Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398573 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398573 :: a) = (-@#@$$) a6989586621679398573
type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679398561 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679398561 :: a) = SubtractSym1 a6989586621679398561
type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679129674 :: k) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679129674 :: k) = DefaultEqSym1 a6989586621679129674
type Apply ((<=?@#@$) :: TyFun k (k ~> Bool) -> Type) (a6989586621679370104 :: k) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((<=?@#@$) :: TyFun k (k ~> Bool) -> Type) (a6989586621679370104 :: k) = (<=?@#@$$) a6989586621679370104
type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (x :: k) # 
Instance details

Defined in Data.Singletons

type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (x :: k) = SameKindSym1 x
type Apply (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) (a6989586621680354872 :: Natural) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) (a6989586621680354872 :: Natural) = ReplicateM_Sym1 a6989586621680354872 :: TyFun (m a) (m ()) -> Type
type Apply (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) (a6989586621680354894 :: Natural) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) (a6989586621680354894 :: Natural) = ReplicateMSym1 a6989586621680354894 :: TyFun (m a) (m [a]) -> Type
type Apply (LeftSym0 :: TyFun a (Either a b) -> Type) (a6989586621679050337 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (LeftSym0 :: TyFun a (Either a b) -> Type) (a6989586621679050337 :: a) = 'Left a6989586621679050337 :: Either a b
type Apply ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) (a6989586621679253960 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) (a6989586621679253960 :: a) = (&@#@$$) a6989586621679253960 :: TyFun (a ~> b) b -> Type
type Apply (Bool_Sym1 a6989586621679122246 :: TyFun a (Bool ~> a) -> Type) (a6989586621679122247 :: a) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym1 a6989586621679122246 :: TyFun a (Bool ~> a) -> Type) (a6989586621679122247 :: a) = Bool_Sym2 a6989586621679122246 a6989586621679122247
type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679544349 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679544349 :: a) = LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type
type Apply (DeleteBySym1 a6989586621679544773 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544774 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym1 a6989586621679544773 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544774 :: a) = DeleteBySym2 a6989586621679544773 a6989586621679544774
type Apply (InsertBySym1 a6989586621679544731 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544732 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym1 a6989586621679544731 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544732 :: a) = InsertBySym2 a6989586621679544731 a6989586621679544732
type Apply (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807410 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807410 :: a) = ShowsPrecSym2 a6989586621679807409 a6989586621679807410
type Apply (EnumFromThenToSym1 a6989586621679414073 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414074 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679414073 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414074 :: a) = EnumFromThenToSym2 a6989586621679414073 a6989586621679414074
type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680159057 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680159057 :: a) = ArgSym1 a6989586621680159057 :: TyFun b (Arg a b) -> Type
type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679050782 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679050782 :: a) = Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type
type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679154354 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679154354 :: a) = ConstSym1 a6989586621679154354 :: TyFun b a -> Type
type Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) (a6989586621679154272 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) (a6989586621679154272 :: a) = SeqSym1 a6989586621679154272 :: TyFun b b -> Type
type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621679900552 :: a) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621679900552 :: a) = AsProxyTypeOfSym1 a6989586621679900552 :: TyFun (proxy a) a -> Type
type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922567 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922567 :: a) = ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type
type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922306 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922306 :: a) = NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type
type Apply (RightSym0 :: TyFun b (Either a b) -> Type) (a6989586621679050339 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (RightSym0 :: TyFun b (Either a b) -> Type) (a6989586621679050339 :: b) = 'Right a6989586621679050339 :: Either a b
type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679387993 :: b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679387993 :: b) = Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type
type Apply (IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type) (a6989586621679124437 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type) (a6989586621679124437 :: k) = IfSym2 a6989586621679124436 a6989586621679124437
type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679050813 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679050813 :: a) = Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type
type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679271232 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679271232 :: a) = (<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type
type Apply (ArgSym1 a6989586621680159057 :: TyFun b (Arg a b) -> Type) (a6989586621680159058 :: b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (ArgSym1 a6989586621680159057 :: TyFun b (Arg a b) -> Type) (a6989586621680159058 :: b) = 'Arg a6989586621680159057 a6989586621680159058
type Apply (ScanlSym1 a6989586621680287221 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287222 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym1 a6989586621680287221 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287222 :: b) = ScanlSym2 a6989586621680287221 a6989586621680287222
type Apply (ScanrSym1 a6989586621680287209 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287210 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym1 a6989586621680287209 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287210 :: b) = ScanrSym2 a6989586621680287209 a6989586621680287210
type Apply (ScanlSym1 a6989586621679545226 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545227 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym1 a6989586621679545226 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545227 :: b) = ScanlSym2 a6989586621679545226 a6989586621679545227
type Apply (ScanrSym1 a6989586621679545199 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545200 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym1 a6989586621679545199 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545200 :: b) = ScanrSym2 a6989586621679545199 a6989586621679545200
type Apply (ComparingSym1 a6989586621679189957 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679189958 :: b) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym1 a6989586621679189957 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679189958 :: b) = ComparingSym2 a6989586621679189957 a6989586621679189958
type Apply (Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type) (a6989586621679050783 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type) (a6989586621679050783 :: b) = '(a6989586621679050782, a6989586621679050783)
type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679050862 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679050862 :: a) = Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type
type Apply (CurrySym1 a6989586621679147661 :: TyFun a (b ~> c) -> Type) (a6989586621679147662 :: a) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym1 a6989586621679147661 :: TyFun a (b ~> c) -> Type) (a6989586621679147662 :: a) = CurrySym2 a6989586621679147661 a6989586621679147662
type Apply (FlipSym1 a6989586621679154327 :: TyFun b (a ~> c) -> Type) (a6989586621679154328 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679154327 :: TyFun b (a ~> c) -> Type) (a6989586621679154328 :: b) = FlipSym2 a6989586621679154327 a6989586621679154328
type Apply (Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679050814 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679050814 :: b) = Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type
type Apply (Foldl'Sym1 a6989586621679922542 :: TyFun b (t a ~> b) -> Type) (a6989586621679922543 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym1 a6989586621679922542 :: TyFun b (t a ~> b) -> Type) (a6989586621679922543 :: b) = Foldl'Sym2 a6989586621679922542 a6989586621679922543 :: TyFun (t a) b -> Type
type Apply (FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type) (a6989586621679922536 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type) (a6989586621679922536 :: b) = FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type
type Apply (Foldr'Sym1 a6989586621679922528 :: TyFun b (t a ~> b) -> Type) (a6989586621679922529 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym1 a6989586621679922528 :: TyFun b (t a ~> b) -> Type) (a6989586621679922529 :: b) = Foldr'Sym2 a6989586621679922528 a6989586621679922529 :: TyFun (t a) b -> Type
type Apply (FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type) (a6989586621679922522 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type) (a6989586621679922522 :: b) = FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type
type Apply (OnSym2 a6989586621679253973 a6989586621679253974 :: TyFun a (a ~> c) -> Type) (a6989586621679253975 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym2 a6989586621679253973 a6989586621679253974 :: TyFun a (a ~> c) -> Type) (a6989586621679253975 :: a) = OnSym3 a6989586621679253973 a6989586621679253974 a6989586621679253975
type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679050931 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679050931 :: a) = Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type
type Apply (MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103083 :: a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103083 :: a) = MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type
type Apply (MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103073 :: a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103073 :: a) = MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type
type Apply (Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679050863 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679050863 :: b) = Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type
type Apply (FoldlMSym1 a6989586621679922477 :: TyFun b (t a ~> m b) -> Type) (a6989586621679922478 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym1 a6989586621679922477 :: TyFun b (t a ~> m b) -> Type) (a6989586621679922478 :: b) = FoldlMSym2 a6989586621679922477 a6989586621679922478 :: TyFun (t a) (m b) -> Type
type Apply (FoldrMSym1 a6989586621679922495 :: TyFun b (t a ~> m b) -> Type) (a6989586621679922496 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym1 a6989586621679922495 :: TyFun b (t a ~> m b) -> Type) (a6989586621679922496 :: b) = FoldrMSym2 a6989586621679922495 a6989586621679922496 :: TyFun (t a) (m b) -> Type
type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679051022 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679051022 :: a) = Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type
type Apply (Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679050932 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679050932 :: b) = Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type
type Apply (Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679050864 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679050864 :: c) = Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type
type Apply (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) (a6989586621679051137 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) (a6989586621679051137 :: a) = Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type
type Apply (Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679051023 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679051023 :: b) = Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type
type Apply (Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679050933 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679050933 :: c) = Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type
type Apply (Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679051138 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679051138 :: b) = Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type
type Apply (Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679051024 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679051024 :: c) = Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type
type Apply (Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679050934 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679050934 :: d) = Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type
type Apply (Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679051139 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679051139 :: c) = Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type
type Apply (Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679051025 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679051025 :: d) = Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type
type Apply (Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679051140 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679051140 :: d) = Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type
type Apply (Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679051026 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679051026 :: e) = Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type
type Apply (Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679051141 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679051141 :: e) = Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type
type Apply (Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679051142 :: f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679051142 :: f) = Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type
type Apply (ConstSym0 :: TyFun a (Const a b) -> Type) (a6989586621680067841 :: a) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Apply (ConstSym0 :: TyFun a (Const a b) -> Type) (a6989586621680067841 :: a) = 'Const a6989586621680067841 :: Const a b
type Apply (Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type) (a6989586621679050815 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type) (a6989586621679050815 :: c) = '(a6989586621679050813, a6989586621679050814, a6989586621679050815)
type Apply (Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type) (a6989586621679050865 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type) (a6989586621679050865 :: d) = '(a6989586621679050862, a6989586621679050863, a6989586621679050864, a6989586621679050865)
type Apply (Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type) (a6989586621679050935 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type) (a6989586621679050935 :: e) = '(a6989586621679050931, a6989586621679050932, a6989586621679050933, a6989586621679050934, a6989586621679050935)
type Apply (Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type) (a6989586621679051027 :: f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type) (a6989586621679051027 :: f) = '(a6989586621679051022, a6989586621679051023, a6989586621679051024, a6989586621679051025, a6989586621679051026, a6989586621679051027)
type Apply (Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type) (a6989586621679051143 :: g) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type) (a6989586621679051143 :: g) = '(a6989586621679051137, a6989586621679051138, a6989586621679051139, a6989586621679051140, a6989586621679051141, a6989586621679051142, a6989586621679051143)
type Apply XorSym0 (a6989586621680287370 :: NonEmpty Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply XorSym0 (a6989586621680287370 :: NonEmpty Bool) = Xor a6989586621680287370
type Apply UnlinesSym0 (a6989586621679544819 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnlinesSym0 (a6989586621679544819 :: [Symbol]) = Unlines a6989586621679544819
type Apply UnwordsSym0 (a6989586621679544809 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnwordsSym0 (a6989586621679544809 :: [Symbol]) = Unwords a6989586621679544809
type Apply (GetFirstSym0 :: TyFun (First a) a -> Type) (a6989586621679458705 :: First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetFirstSym0 :: TyFun (First a) a -> Type) (a6989586621679458705 :: First a) = GetFirst a6989586621679458705
type Apply (GetLastSym0 :: TyFun (Last a) a -> Type) (a6989586621679458724 :: Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetLastSym0 :: TyFun (Last a) a -> Type) (a6989586621679458724 :: Last a) = GetLast a6989586621679458724
type Apply (GetMaxSym0 :: TyFun (Max a) a -> Type) (a6989586621679458686 :: Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetMaxSym0 :: TyFun (Max a) a -> Type) (a6989586621679458686 :: Max a) = GetMax a6989586621679458686
type Apply (GetMinSym0 :: TyFun (Min a) a -> Type) (a6989586621679458667 :: Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetMinSym0 :: TyFun (Min a) a -> Type) (a6989586621679458667 :: Min a) = GetMin a6989586621679458667
type Apply (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) (a6989586621679458743 :: WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) (a6989586621679458743 :: WrappedMonoid m) = UnwrapMonoid a6989586621679458743
type Apply (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) (a6989586621680287381 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) (a6989586621680287381 :: NonEmpty a) = Length a6989586621680287381
type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621680287316 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (HeadSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621680287316 :: NonEmpty a) = Head a6989586621680287316
type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621680287307 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (LastSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621680287307 :: NonEmpty a) = Last a6989586621680287307
type Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621679173983 :: NonEmpty a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621679173983 :: NonEmpty a) = Sconcat a6989586621679173983
type Apply (RunIdentitySym0 :: TyFun (Identity a) a -> Type) (a6989586621679051207 :: Identity a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (RunIdentitySym0 :: TyFun (Identity a) a -> Type) (a6989586621679051207 :: Identity a) = RunIdentity a6989586621679051207
type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679198738 :: Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679198738 :: Down a) = GetDown a6989586621679198738
type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679458578 :: Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679458578 :: Dual a) = GetDual a6989586621679458578
type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679458648 :: Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679458648 :: Product a) = GetProduct a6989586621679458648
type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679458629 :: Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679458629 :: Sum a) = GetSum a6989586621679458629
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679390233 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679390233 :: Maybe a) = IsJust a6989586621679390233
type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679390230 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679390230 :: Maybe a) = IsNothing a6989586621679390230
type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679390226 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (FromJustSym0 :: TyFun (Maybe a) a -> Type) (a6989586621679390226 :: Maybe a) = FromJust a6989586621679390226
type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679545466 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679545466 :: [a]) = Head a6989586621679545466
type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679545460 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679545460 :: [a]) = Last a6989586621679545460
type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621679860750 :: [a]) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621679860750 :: [a]) = Mconcat a6989586621679860750
type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621679922378 :: t Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621679922378 :: t Bool) = And a6989586621679922378
type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621679922372 :: t Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621679922372 :: t Bool) = Or a6989586621679922372
type Apply (IsPrefixOfSym1 a6989586621680286965 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621680286966 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym1 a6989586621680286965 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621680286966 :: NonEmpty a) = IsPrefixOf a6989586621680286965 a6989586621680286966
type Apply (FromMaybeSym1 a6989586621679390214 :: TyFun (Maybe a) a -> Type) (a6989586621679390215 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (FromMaybeSym1 a6989586621679390214 :: TyFun (Maybe a) a -> Type) (a6989586621679390215 :: Maybe a) = FromMaybe a6989586621679390214 a6989586621679390215
type Apply (IsInfixOfSym1 a6989586621679545011 :: TyFun [a] Bool -> Type) (a6989586621679545012 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsInfixOfSym1 a6989586621679545011 :: TyFun [a] Bool -> Type) (a6989586621679545012 :: [a]) = IsInfixOf a6989586621679545011 a6989586621679545012
type Apply (IsPrefixOfSym1 a6989586621679545025 :: TyFun [a] Bool -> Type) (a6989586621679545026 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsPrefixOfSym1 a6989586621679545025 :: TyFun [a] Bool -> Type) (a6989586621679545026 :: [a]) = IsPrefixOf a6989586621679545025 a6989586621679545026
type Apply (IsSuffixOfSym1 a6989586621679545018 :: TyFun [a] Bool -> Type) (a6989586621679545019 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsSuffixOfSym1 a6989586621679545018 :: TyFun [a] Bool -> Type) (a6989586621679545019 :: [a]) = IsSuffixOf a6989586621679545018 a6989586621679545019
type Apply (Foldl1'Sym1 a6989586621679545295 :: TyFun [a] a -> Type) (a6989586621679545296 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Foldl1'Sym1 a6989586621679545295 :: TyFun [a] a -> Type) (a6989586621679545296 :: [a]) = Foldl1' a6989586621679545295 a6989586621679545296
type Apply (GenericLengthSym0 :: TyFun [a] i -> Type) (a6989586621679544194 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GenericLengthSym0 :: TyFun [a] i -> Type) (a6989586621679544194 :: [a]) = GenericLength a6989586621679544194 :: i
type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621679922563 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621679922563 :: t a) = Length a6989586621679922563
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621679922560 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621679922560 :: t a) = Null a6989586621679922560
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621679922571 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621679922571 :: t a) = Maximum a6989586621679922571
type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621679922574 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621679922574 :: t a) = Minimum a6989586621679922574
type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621679922580 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621679922580 :: t a) = Product a6989586621679922580
type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621679922577 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621679922577 :: t a) = Sum a6989586621679922577
type Apply (FoldSym0 :: TyFun (t m) m -> Type) (a6989586621679922511 :: t m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldSym0 :: TyFun (t m) m -> Type) (a6989586621679922511 :: t m) = Fold a6989586621679922511
type Apply (AsProxyTypeOfSym1 a6989586621679900552 :: TyFun (proxy a) a -> Type) (a6989586621679900553 :: proxy a) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Apply (AsProxyTypeOfSym1 a6989586621679900552 :: TyFun (proxy a) a -> Type) (a6989586621679900553 :: proxy a) = AsProxyTypeOf a6989586621679900552 a6989586621679900553
type Apply (AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type) (a6989586621679922356 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type) (a6989586621679922356 :: t a) = All a6989586621679922355 a6989586621679922356
type Apply (AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type) (a6989586621679922365 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type) (a6989586621679922365 :: t a) = Any a6989586621679922364 a6989586621679922365
type Apply (ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type) (a6989586621679922568 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type) (a6989586621679922568 :: t a) = Elem a6989586621679922567 a6989586621679922568
type Apply (NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type) (a6989586621679922307 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type) (a6989586621679922307 :: t a) = NotElem a6989586621679922306 a6989586621679922307
type Apply (Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type) (a6989586621679922554 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type) (a6989586621679922554 :: t a) = Foldl1 a6989586621679922553 a6989586621679922554
type Apply (Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type) (a6989586621679922549 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type) (a6989586621679922549 :: t a) = Foldr1 a6989586621679922548 a6989586621679922549
type Apply (MaximumBySym1 a6989586621679922335 :: TyFun (t a) a -> Type) (a6989586621679922336 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym1 a6989586621679922335 :: TyFun (t a) a -> Type) (a6989586621679922336 :: t a) = MaximumBy a6989586621679922335 a6989586621679922336
type Apply (MinimumBySym1 a6989586621679922315 :: TyFun (t a) a -> Type) (a6989586621679922316 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym1 a6989586621679922315 :: TyFun (t a) a -> Type) (a6989586621679922316 :: t a) = MinimumBy a6989586621679922315 a6989586621679922316
type Apply (Maybe_Sym2 a6989586621679387993 a6989586621679387994 :: TyFun (Maybe a) b -> Type) (a6989586621679387995 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym2 a6989586621679387993 a6989586621679387994 :: TyFun (Maybe a) b -> Type) (a6989586621679387995 :: Maybe a) = Maybe_ a6989586621679387993 a6989586621679387994 a6989586621679387995
type Apply (FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type) (a6989586621679922516 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type) (a6989586621679922516 :: t a) = FoldMap a6989586621679922515 a6989586621679922516
type Apply (FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type) (a6989586621680103040 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type) (a6989586621680103040 :: t a) = FoldMapDefault a6989586621680103039 a6989586621680103040
type Apply (Foldl'Sym2 a6989586621679922542 a6989586621679922543 :: TyFun (t a) b -> Type) (a6989586621679922544 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym2 a6989586621679922542 a6989586621679922543 :: TyFun (t a) b -> Type) (a6989586621679922544 :: t a) = Foldl' a6989586621679922542 a6989586621679922543 a6989586621679922544
type Apply (FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type) (a6989586621679922537 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type) (a6989586621679922537 :: t a) = Foldl a6989586621679922535 a6989586621679922536 a6989586621679922537
type Apply (Foldr'Sym2 a6989586621679922528 a6989586621679922529 :: TyFun (t a) b -> Type) (a6989586621679922530 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym2 a6989586621679922528 a6989586621679922529 :: TyFun (t a) b -> Type) (a6989586621679922530 :: t a) = Foldr' a6989586621679922528 a6989586621679922529 a6989586621679922530
type Apply (FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type) (a6989586621679922523 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type) (a6989586621679922523 :: t a) = Foldr a6989586621679922521 a6989586621679922522 a6989586621679922523
type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286864 :: NonEmpty (NonEmpty a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286864 :: NonEmpty (NonEmpty a)) = Transpose a6989586621680286864
type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680287023 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680287023 :: NonEmpty a) = Group1 a6989586621680287023
type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286884 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286884 :: NonEmpty a) = Nub a6989586621680286884
type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287172 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287172 :: NonEmpty a) = Reverse a6989586621680287172
type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287279 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287279 :: NonEmpty a) = Sort a6989586621680287279
type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287302 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287302 :: NonEmpty a) = Init a6989586621680287302
type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287312 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287312 :: NonEmpty a) = Tail a6989586621680287312
type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287267 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287267 :: NonEmpty a) = ToList a6989586621680287267
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621679864300 :: First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621679864300 :: First a) = GetFirst a6989586621679864300
type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621679864323 :: Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621679864323 :: Last a) = GetLast a6989586621679864323
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621679864297 :: Maybe a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621679864297 :: Maybe a) = 'First a6989586621679864297
type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621679864320 :: Maybe a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621679864320 :: Maybe a) = 'Last a6989586621679864320
type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679390209 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) (a6989586621679390209 :: Maybe a) = MaybeToList a6989586621679390209
type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679390199 :: [Maybe a]) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) (a6989586621679390199 :: [Maybe a]) = CatMaybes a6989586621679390199
type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679544278 :: [[a]]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) (a6989586621679544278 :: [[a]]) = Transpose a6989586621679544278
type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621680287246 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621680287246 :: [a]) = Inits a6989586621680287246
type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621680287240 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) (a6989586621680287240 :: [a]) = Tails a6989586621680287240
type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680287272 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680287272 :: [a]) = FromList a6989586621680287272
type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621680287350 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) (a6989586621680287350 :: [a]) = NonEmpty_ a6989586621680287350
type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679390205 :: [a]) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) (a6989586621679390205 :: [a]) = ListToMaybe a6989586621679390205
type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287085 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287085 :: [a]) = Group a6989586621680287085
type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679544420 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GroupSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679544420 :: [a]) = Group a6989586621679544420
type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679545043 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InitsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679545043 :: [a]) = Inits a6989586621679545043
type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679545330 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (PermutationsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679545330 :: [a]) = Permutations a6989586621679545330
type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679545410 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679545410 :: [a]) = Subsequences a6989586621679545410
type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679545033 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TailsSym0 :: TyFun [a] [[a]] -> Type) (a6989586621679545033 :: [a]) = Tails a6989586621679545033
type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679545444 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679545444 :: [a]) = Init a6989586621679545444
type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679544249 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NubSym0 :: TyFun [a] [a] -> Type) (a6989586621679544249 :: [a]) = Nub a6989586621679544249
type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679545429 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679545429 :: [a]) = Reverse a6989586621679545429
type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679544395 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SortSym0 :: TyFun [a] [a] -> Type) (a6989586621679544395 :: [a]) = Sort a6989586621679544395
type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679545456 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679545456 :: [a]) = Tail a6989586621679545456
type Apply (GroupBy1Sym1 a6989586621680286992 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286993 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym1 a6989586621680286992 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286993 :: NonEmpty a) = GroupBy1 a6989586621680286992 a6989586621680286993
type Apply ((<|@#@$$) a6989586621680287295 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287296 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((<|@#@$$) a6989586621680287295 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287296 :: NonEmpty a) = a6989586621680287295 <| a6989586621680287296
type Apply (ConsSym1 a6989586621680287288 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287289 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym1 a6989586621680287288 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287289 :: NonEmpty a) = Cons a6989586621680287288 a6989586621680287289
type Apply (IntersperseSym1 a6989586621680287177 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287178 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym1 a6989586621680287177 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287178 :: NonEmpty a) = Intersperse a6989586621680287177 a6989586621680287178
type Apply (NubBySym1 a6989586621680286869 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286870 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym1 a6989586621680286869 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286870 :: NonEmpty a) = NubBy a6989586621680286869 a6989586621680286870
type Apply (Scanl1Sym1 a6989586621680287198 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287199 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym1 a6989586621680287198 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287199 :: NonEmpty a) = Scanl1 a6989586621680287198 a6989586621680287199
type Apply (Scanr1Sym1 a6989586621680287190 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287191 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym1 a6989586621680287190 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680287191 :: NonEmpty a) = Scanr1 a6989586621680287190 a6989586621680287191
type Apply (SortBySym1 a6989586621680286856 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286857 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym1 a6989586621680286856 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286857 :: NonEmpty a) = SortBy a6989586621680286856 a6989586621680286857
type Apply (DropSym1 a6989586621680287155 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287156 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropSym1 a6989586621680287155 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287156 :: NonEmpty a) = Drop a6989586621680287155 a6989586621680287156
type Apply (DropWhileSym1 a6989586621680287128 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287129 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym1 a6989586621680287128 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287129 :: NonEmpty a) = DropWhile a6989586621680287128 a6989586621680287129
type Apply (FilterSym1 a6989586621680287101 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287102 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym1 a6989586621680287101 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287102 :: NonEmpty a) = Filter a6989586621680287101 a6989586621680287102
type Apply (TakeSym1 a6989586621680287164 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287165 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeSym1 a6989586621680287164 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287165 :: NonEmpty a) = Take a6989586621680287164 a6989586621680287165
type Apply (TakeWhileSym1 a6989586621680287137 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287138 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym1 a6989586621680287137 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621680287138 :: NonEmpty a) = TakeWhile a6989586621680287137 a6989586621680287138
type Apply ((:$$:@#@$$) a6989586621679803713 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621679803714 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply ((:$$:@#@$$) a6989586621679803713 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621679803714 :: ErrorMessage' s) = a6989586621679803713 ':$$: a6989586621679803714
type Apply ((:<>:@#@$$) a6989586621679803710 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621679803711 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply ((:<>:@#@$$) a6989586621679803710 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621679803711 :: ErrorMessage' s) = a6989586621679803710 ':<>: a6989586621679803711
type Apply (LeftsSym0 :: TyFun [Either a b] [a] -> Type) (a6989586621679261623 :: [Either a b]) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (LeftsSym0 :: TyFun [Either a b] [a] -> Type) (a6989586621679261623 :: [Either a b]) = Lefts a6989586621679261623
type Apply (RightsSym0 :: TyFun [Either a b] [b] -> Type) (a6989586621679261617 :: [Either a b]) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (RightsSym0 :: TyFun [Either a b] [b] -> Type) (a6989586621679261617 :: [Either a b]) = Rights a6989586621679261617
type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679365940 :: [Char]) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679365940 :: [Char]) = Fail a6989586621679365940 :: m a
type Apply (IntercalateSym1 a6989586621679545415 :: TyFun [[a]] [a] -> Type) (a6989586621679545416 :: [[a]]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntercalateSym1 a6989586621679545415 :: TyFun [[a]] [a] -> Type) (a6989586621679545416 :: [[a]]) = Intercalate a6989586621679545415 a6989586621679545416
type Apply (InsertSym1 a6989586621680287232 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680287233 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InsertSym1 a6989586621680287232 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621680287233 :: [a]) = Insert a6989586621680287232 a6989586621680287233
type Apply ((:|@#@$$) a6989586621679050362 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679050363 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$$) a6989586621679050362 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679050363 :: [a]) = a6989586621679050362 ':| a6989586621679050363
type Apply (ElemIndexSym1 a6989586621679544658 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679544659 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndexSym1 a6989586621679544658 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679544659 :: [a]) = ElemIndex a6989586621679544658 a6989586621679544659
type Apply (FindIndexSym1 a6989586621679544640 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679544641 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym1 a6989586621679544640 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679544641 :: [a]) = FindIndex a6989586621679544640 a6989586621679544641
type Apply (StripPrefixSym1 a6989586621679656297 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679656298 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (StripPrefixSym1 a6989586621679656297 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679656298 :: [a]) = StripPrefix a6989586621679656297 a6989586621679656298
type Apply (GroupBySym1 a6989586621680287048 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287049 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym1 a6989586621680287048 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287049 :: [a]) = GroupBy a6989586621680287048 a6989586621680287049
type Apply (ElemIndicesSym1 a6989586621679544649 :: TyFun [a] [Natural] -> Type) (a6989586621679544650 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndicesSym1 a6989586621679544649 :: TyFun [a] [Natural] -> Type) (a6989586621679544650 :: [a]) = ElemIndices a6989586621679544649 a6989586621679544650
type Apply (FindIndicesSym1 a6989586621679544619 :: TyFun [a] [Natural] -> Type) (a6989586621679544620 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndicesSym1 a6989586621679544619 :: TyFun [a] [Natural] -> Type) (a6989586621679544620 :: [a]) = FindIndices a6989586621679544619 a6989586621679544620
type Apply (GroupBySym1 a6989586621679544364 :: TyFun [a] [[a]] -> Type) (a6989586621679544365 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GroupBySym1 a6989586621679544364 :: TyFun [a] [[a]] -> Type) (a6989586621679544365 :: [a]) = GroupBy a6989586621679544364 a6989586621679544365
type Apply (DeleteSym1 a6989586621679544803 :: TyFun [a] [a] -> Type) (a6989586621679544804 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteSym1 a6989586621679544803 :: TyFun [a] [a] -> Type) (a6989586621679544804 :: [a]) = Delete a6989586621679544803 a6989586621679544804
type Apply (DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type) (a6989586621679544433 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type) (a6989586621679544433 :: [a]) = Drop a6989586621679544432 a6989586621679544433
type Apply (DropWhileEndSym1 a6989586621679544538 :: TyFun [a] [a] -> Type) (a6989586621679544539 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym1 a6989586621679544538 :: TyFun [a] [a] -> Type) (a6989586621679544539 :: [a]) = DropWhileEnd a6989586621679544538 a6989586621679544539
type Apply (DropWhileSym1 a6989586621679544559 :: TyFun [a] [a] -> Type) (a6989586621679544560 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym1 a6989586621679544559 :: TyFun [a] [a] -> Type) (a6989586621679544560 :: [a]) = DropWhile a6989586621679544559 a6989586621679544560
type Apply (FilterSym1 a6989586621679544674 :: TyFun [a] [a] -> Type) (a6989586621679544675 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym1 a6989586621679544674 :: TyFun [a] [a] -> Type) (a6989586621679544675 :: [a]) = Filter a6989586621679544674 a6989586621679544675
type Apply (InsertSym1 a6989586621679544400 :: TyFun [a] [a] -> Type) (a6989586621679544401 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertSym1 a6989586621679544400 :: TyFun [a] [a] -> Type) (a6989586621679544401 :: [a]) = Insert a6989586621679544400 a6989586621679544401
type Apply (IntersectSym1 a6989586621679544612 :: TyFun [a] [a] -> Type) (a6989586621679544613 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectSym1 a6989586621679544612 :: TyFun [a] [a] -> Type) (a6989586621679544613 :: [a]) = Intersect a6989586621679544612 a6989586621679544613
type Apply (IntersperseSym1 a6989586621679545422 :: TyFun [a] [a] -> Type) (a6989586621679545423 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersperseSym1 a6989586621679545422 :: TyFun [a] [a] -> Type) (a6989586621679545423 :: [a]) = Intersperse a6989586621679545422 a6989586621679545423
type Apply (NubBySym1 a6989586621679544231 :: TyFun [a] [a] -> Type) (a6989586621679544232 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NubBySym1 a6989586621679544231 :: TyFun [a] [a] -> Type) (a6989586621679544232 :: [a]) = NubBy a6989586621679544231 a6989586621679544232
type Apply (Scanl1Sym1 a6989586621679545217 :: TyFun [a] [a] -> Type) (a6989586621679545218 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym1 a6989586621679545217 :: TyFun [a] [a] -> Type) (a6989586621679545218 :: [a]) = Scanl1 a6989586621679545217 a6989586621679545218
type Apply (Scanr1Sym1 a6989586621679545179 :: TyFun [a] [a] -> Type) (a6989586621679545180 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym1 a6989586621679545179 :: TyFun [a] [a] -> Type) (a6989586621679545180 :: [a]) = Scanr1 a6989586621679545179 a6989586621679545180
type Apply (SortBySym1 a6989586621679544751 :: TyFun [a] [a] -> Type) (a6989586621679544752 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SortBySym1 a6989586621679544751 :: TyFun [a] [a] -> Type) (a6989586621679544752 :: [a]) = SortBy a6989586621679544751 a6989586621679544752
type Apply (TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type) (a6989586621679544446 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type) (a6989586621679544446 :: [a]) = Take a6989586621679544445 a6989586621679544446
type Apply (TakeWhileSym1 a6989586621679544574 :: TyFun [a] [a] -> Type) (a6989586621679544575 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym1 a6989586621679544574 :: TyFun [a] [a] -> Type) (a6989586621679544575 :: [a]) = TakeWhile a6989586621679544574 a6989586621679544575
type Apply (UnionSym1 a6989586621679544203 :: TyFun [a] [a] -> Type) (a6989586621679544204 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionSym1 a6989586621679544203 :: TyFun [a] [a] -> Type) (a6989586621679544204 :: [a]) = Union a6989586621679544203 a6989586621679544204
type Apply ((\\@#@$$) a6989586621679544792 :: TyFun [a] [a] -> Type) (a6989586621679544793 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((\\@#@$$) a6989586621679544792 :: TyFun [a] [a] -> Type) (a6989586621679544793 :: [a]) = a6989586621679544792 \\ a6989586621679544793
type Apply ((:@#@$$) a6989586621679050289 :: TyFun [a] [a] -> Type) (a6989586621679050290 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$$) a6989586621679050289 :: TyFun [a] [a] -> Type) (a6989586621679050290 :: [a]) = a6989586621679050289 ': a6989586621679050290
type Apply ((++@#@$$) a6989586621679154364 :: TyFun [a] [a] -> Type) (a6989586621679154365 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$$) a6989586621679154364 :: TyFun [a] [a] -> Type) (a6989586621679154365 :: [a]) = a6989586621679154364 ++ a6989586621679154365
type Apply (UnlessSym1 a6989586621680354860 :: TyFun (f ()) (f ()) -> Type) (a6989586621680354861 :: f ()) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (UnlessSym1 a6989586621680354860 :: TyFun (f ()) (f ()) -> Type) (a6989586621680354861 :: f ()) = Unless a6989586621680354860 a6989586621680354861
type Apply (WhenSym1 a6989586621679271164 :: TyFun (f ()) (f ()) -> Type) (a6989586621679271165 :: f ()) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (WhenSym1 a6989586621679271164 :: TyFun (f ()) (f ()) -> Type) (a6989586621679271165 :: f ()) = When a6989586621679271164 a6989586621679271165
type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621680340908 :: f a) Source # 
Instance details

Defined in Control.Applicative.Singletons

type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621680340908 :: f a) = Optional a6989586621680340908
type Apply (VoidSym0 :: TyFun (f a) (f ()) -> Type) (a6989586621679357493 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (VoidSym0 :: TyFun (f a) (f ()) -> Type) (a6989586621679357493 :: f a) = Void a6989586621679357493
type Apply (JoinSym0 :: TyFun (m (m a)) (m a) -> Type) (a6989586621679271182 :: m (m a)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (JoinSym0 :: TyFun (m (m a)) (m a) -> Type) (a6989586621679271182 :: m (m a)) = Join a6989586621679271182
type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621679922398 :: t [a]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621679922398 :: t [a]) = Concat a6989586621679922398
type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (a6989586621679922557 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (a6989586621679922557 :: t a) = ToList a6989586621679922557
type Apply (GroupAllWith1Sym1 a6989586621680286976 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286977 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym1 a6989586621680286976 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286977 :: NonEmpty a) = GroupAllWith1 a6989586621680286976 a6989586621680286977
type Apply (GroupWith1Sym1 a6989586621680286985 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286986 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym1 a6989586621680286985 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621680286986 :: NonEmpty a) = GroupWith1 a6989586621680286985 a6989586621680286986
type Apply (SortWithSym1 a6989586621680286847 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286848 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym1 a6989586621680286847 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621680286848 :: NonEmpty a) = SortWith a6989586621680286847 a6989586621680286848
type Apply (MapSym1 a6989586621680287251 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621680287252 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym1 a6989586621680287251 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621680287252 :: NonEmpty a) = Map a6989586621680287251 a6989586621680287252
type Apply (ZipSym1 a6989586621680286929 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621680286930 :: NonEmpty b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym1 a6989586621680286929 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621680286930 :: NonEmpty b) = Zip a6989586621680286929 a6989586621680286930
type Apply (LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679544350 :: [(a, b)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679544350 :: [(a, b)]) = Lookup a6989586621679544349 a6989586621679544350
type Apply (GroupAllWithSym1 a6989586621680287030 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287031 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym1 a6989586621680287030 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287031 :: [a]) = GroupAllWith a6989586621680287030 a6989586621680287031
type Apply (GroupWithSym1 a6989586621680287039 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287040 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym1 a6989586621680287039 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621680287040 :: [a]) = GroupWith a6989586621680287039 a6989586621680287040
type Apply (DeleteBySym2 a6989586621679544773 a6989586621679544774 :: TyFun [a] [a] -> Type) (a6989586621679544775 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym2 a6989586621679544773 a6989586621679544774 :: TyFun [a] [a] -> Type) (a6989586621679544775 :: [a]) = DeleteBy a6989586621679544773 a6989586621679544774 a6989586621679544775
type Apply (DeleteFirstsBySym2 a6989586621679544763 a6989586621679544764 :: TyFun [a] [a] -> Type) (a6989586621679544765 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym2 a6989586621679544763 a6989586621679544764 :: TyFun [a] [a] -> Type) (a6989586621679544765 :: [a]) = DeleteFirstsBy a6989586621679544763 a6989586621679544764 a6989586621679544765
type Apply (InsertBySym2 a6989586621679544731 a6989586621679544732 :: TyFun [a] [a] -> Type) (a6989586621679544733 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym2 a6989586621679544731 a6989586621679544732 :: TyFun [a] [a] -> Type) (a6989586621679544733 :: [a]) = InsertBy a6989586621679544731 a6989586621679544732 a6989586621679544733
type Apply (IntersectBySym2 a6989586621679544588 a6989586621679544589 :: TyFun [a] [a] -> Type) (a6989586621679544590 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym2 a6989586621679544588 a6989586621679544589 :: TyFun [a] [a] -> Type) (a6989586621679544590 :: [a]) = IntersectBy a6989586621679544588 a6989586621679544589 a6989586621679544590
type Apply (UnionBySym2 a6989586621679544211 a6989586621679544212 :: TyFun [a] [a] -> Type) (a6989586621679544213 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym2 a6989586621679544211 a6989586621679544212 :: TyFun [a] [a] -> Type) (a6989586621679544213 :: [a]) = UnionBy a6989586621679544211 a6989586621679544212 a6989586621679544213
type Apply (MapMaybeSym1 a6989586621679390184 :: TyFun [a] [b] -> Type) (a6989586621679390185 :: [a]) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MapMaybeSym1 a6989586621679390184 :: TyFun [a] [b] -> Type) (a6989586621679390185 :: [a]) = MapMaybe a6989586621679390184 a6989586621679390185
type Apply (MapSym1 a6989586621679154373 :: TyFun [a] [b] -> Type) (a6989586621679154374 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym1 a6989586621679154373 :: TyFun [a] [b] -> Type) (a6989586621679154374 :: [a]) = Map a6989586621679154373 a6989586621679154374
type Apply (FilterMSym1 a6989586621680355005 :: TyFun [a] (m [a]) -> Type) (a6989586621680355006 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (FilterMSym1 a6989586621680355005 :: TyFun [a] (m [a]) -> Type) (a6989586621680355006 :: [a]) = FilterM a6989586621680355005 a6989586621680355006
type Apply (ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type) (a6989586621679544987 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type) (a6989586621679544987 :: [b]) = Zip a6989586621679544986 a6989586621679544987
type Apply ((<|>@#@$$) a6989586621679271374 :: TyFun (f a) (f a) -> Type) (a6989586621679271375 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<|>@#@$$) a6989586621679271374 :: TyFun (f a) (f a) -> Type) (a6989586621679271375 :: f a) = a6989586621679271374 <|> a6989586621679271375
type Apply (ReplicateM_Sym1 a6989586621680354872 :: TyFun (m a) (m ()) -> Type) (a6989586621680354873 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ReplicateM_Sym1 a6989586621680354872 :: TyFun (m a) (m ()) -> Type) (a6989586621680354873 :: m a) = ReplicateM_ a6989586621680354872 a6989586621680354873
type Apply (ReplicateMSym1 a6989586621680354894 :: TyFun (m a) (m [a]) -> Type) (a6989586621680354895 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ReplicateMSym1 a6989586621680354894 :: TyFun (m a) (m [a]) -> Type) (a6989586621680354895 :: m a) = ReplicateM a6989586621680354894 a6989586621680354895
type Apply (MfilterSym1 a6989586621680354827 :: TyFun (m a) (m a) -> Type) (a6989586621680354828 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MfilterSym1 a6989586621680354827 :: TyFun (m a) (m a) -> Type) (a6989586621680354828 :: m a) = Mfilter a6989586621680354827 a6989586621680354828
type Apply (MplusSym1 a6989586621679271380 :: TyFun (m a) (m a) -> Type) (a6989586621679271381 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (MplusSym1 a6989586621679271380 :: TyFun (m a) (m a) -> Type) (a6989586621679271381 :: m a) = Mplus a6989586621679271380 a6989586621679271381
type Apply (FindSym1 a6989586621679922286 :: TyFun (t a) (Maybe a) -> Type) (a6989586621679922287 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym1 a6989586621679922286 :: TyFun (t a) (Maybe a) -> Type) (a6989586621679922287 :: t a) = Find a6989586621679922286 a6989586621679922287
type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621679922431 :: t (f a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621679922431 :: t (f a)) = SequenceA_ a6989586621679922431
type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621679922419 :: t (f a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621679922419 :: t (f a)) = Asum a6989586621679922419
type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680096864 :: t (f a)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680096864 :: t (f a)) = SequenceA a6989586621680096864
type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621679922425 :: t (m a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621679922425 :: t (m a)) = Sequence_ a6989586621679922425
type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621679922413 :: t (m a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621679922413 :: t (m a)) = Msum a6989586621679922413
type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680096872 :: t (m a)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680096872 :: t (m a)) = Sequence a6989586621680096872
type Apply (ScanlSym2 a6989586621680287221 a6989586621680287222 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680287223 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym2 a6989586621680287221 a6989586621680287222 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680287223 :: [a]) = Scanl a6989586621680287221 a6989586621680287222 a6989586621680287223
type Apply (ScanrSym2 a6989586621680287209 a6989586621680287210 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680287211 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym2 a6989586621680287209 a6989586621680287210 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621680287211 :: [a]) = Scanr a6989586621680287209 a6989586621680287210 a6989586621680287211
type Apply (ScanlSym2 a6989586621679545226 a6989586621679545227 :: TyFun [a] [b] -> Type) (a6989586621679545228 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym2 a6989586621679545226 a6989586621679545227 :: TyFun [a] [b] -> Type) (a6989586621679545228 :: [a]) = Scanl a6989586621679545226 a6989586621679545227 a6989586621679545228
type Apply (ScanrSym2 a6989586621679545199 a6989586621679545200 :: TyFun [a] [b] -> Type) (a6989586621679545201 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym2 a6989586621679545199 a6989586621679545200 :: TyFun [a] [b] -> Type) (a6989586621679545201 :: [a]) = Scanr a6989586621679545199 a6989586621679545200 a6989586621679545201
type Apply ((<**>@#@$$) a6989586621679271211 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679271212 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<**>@#@$$) a6989586621679271211 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679271212 :: f (a ~> b)) = a6989586621679271211 <**> a6989586621679271212
type Apply ((<*>@#@$$) a6989586621679271255 :: TyFun (f a) (f b) -> Type) (a6989586621679271256 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$$) a6989586621679271255 :: TyFun (f a) (f b) -> Type) (a6989586621679271256 :: f a) = a6989586621679271255 <*> a6989586621679271256
type Apply (FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type) (a6989586621679271228 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type) (a6989586621679271228 :: f a) = Fmap a6989586621679271227 a6989586621679271228
type Apply (LiftASym1 a6989586621679271200 :: TyFun (f a) (f b) -> Type) (a6989586621679271201 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftASym1 a6989586621679271200 :: TyFun (f a) (f b) -> Type) (a6989586621679271201 :: f a) = LiftA a6989586621679271200 a6989586621679271201
type Apply ((<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type) (a6989586621679357521 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type) (a6989586621679357521 :: f a) = a6989586621679357520 <$> a6989586621679357521
type Apply ((<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type) (a6989586621679271233 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type) (a6989586621679271233 :: f b) = a6989586621679271232 <$ a6989586621679271233
type Apply ((<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type) (a6989586621679271273 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type) (a6989586621679271273 :: f b) = a6989586621679271272 <* a6989586621679271273
type Apply ((*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type) (a6989586621679271268 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type) (a6989586621679271268 :: f b) = a6989586621679271267 *> a6989586621679271268
type Apply ((<$!>@#@$$) a6989586621680354845 :: TyFun (m a) (m b) -> Type) (a6989586621680354846 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<$!>@#@$$) a6989586621680354845 :: TyFun (m a) (m b) -> Type) (a6989586621680354846 :: m a) = a6989586621680354845 <$!> a6989586621680354846
type Apply ((=<<@#@$$) a6989586621679271176 :: TyFun (m a) (m b) -> Type) (a6989586621679271177 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$$) a6989586621679271176 :: TyFun (m a) (m b) -> Type) (a6989586621679271177 :: m a) = a6989586621679271176 =<< a6989586621679271177
type Apply (ApSym1 a6989586621679270990 :: TyFun (m a) (m b) -> Type) (a6989586621679270991 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ApSym1 a6989586621679270990 :: TyFun (m a) (m b) -> Type) (a6989586621679270991 :: m a) = Ap a6989586621679270990 a6989586621679270991
type Apply (LiftMSym1 a6989586621679271151 :: TyFun (m a1) (m r) -> Type) (a6989586621679271152 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftMSym1 a6989586621679271151 :: TyFun (m a1) (m r) -> Type) (a6989586621679271152 :: m a1) = LiftM a6989586621679271151 a6989586621679271152
type Apply (MzipSym1 a6989586621680264763 :: TyFun (m b) (m (a, b)) -> Type) (a6989586621680264764 :: m b) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym1 a6989586621680264763 :: TyFun (m b) (m (a, b)) -> Type) (a6989586621680264764 :: m b) = Mzip a6989586621680264763 a6989586621680264764
type Apply ((>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type) (a6989586621679271341 :: m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type) (a6989586621679271341 :: m b) = a6989586621679271340 >> a6989586621679271341
type Apply (ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type) (a6989586621679922384 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type) (a6989586621679922384 :: t a) = ConcatMap a6989586621679922383 a6989586621679922384
type Apply (FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type) (a6989586621680103059 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type) (a6989586621680103059 :: t a) = FmapDefault a6989586621680103058 a6989586621680103059
type Apply (ZipWithSym2 a6989586621680286918 a6989586621680286919 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621680286920 :: NonEmpty b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym2 a6989586621680286918 a6989586621680286919 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621680286920 :: NonEmpty b) = ZipWith a6989586621680286918 a6989586621680286919 a6989586621680286920
type Apply (MapAndUnzipMSym1 a6989586621680354962 :: TyFun [a] (m ([b], [c])) -> Type) (a6989586621680354963 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MapAndUnzipMSym1 a6989586621680354962 :: TyFun [a] (m ([b], [c])) -> Type) (a6989586621680354963 :: [a]) = MapAndUnzipM a6989586621680354962 a6989586621680354963
type Apply (ZipWithSym2 a6989586621679544962 a6989586621679544963 :: TyFun [b] [c] -> Type) (a6989586621679544964 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym2 a6989586621679544962 a6989586621679544963 :: TyFun [b] [c] -> Type) (a6989586621679544964 :: [b]) = ZipWith a6989586621679544962 a6989586621679544963 a6989586621679544964
type Apply (Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679544976 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679544976 :: [c]) = Zip3 a6989586621679544974 a6989586621679544975 a6989586621679544976
type Apply (Traverse_Sym1 a6989586621679922469 :: TyFun (t a) (f ()) -> Type) (a6989586621679922470 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym1 a6989586621679922469 :: TyFun (t a) (f ()) -> Type) (a6989586621679922470 :: t a) = Traverse_ a6989586621679922469 a6989586621679922470
type Apply (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680096861 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680096861 :: t a) = Traverse a6989586621680096860 a6989586621680096861
type Apply (MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type) (a6989586621679922450 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type) (a6989586621679922450 :: t a) = MapM_ a6989586621679922449 a6989586621679922450
type Apply (MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680096869 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680096869 :: t a) = MapM a6989586621680096868 a6989586621680096869
type Apply (ZipWithM_Sym2 a6989586621680354943 a6989586621680354944 :: TyFun [b] (m ()) -> Type) (a6989586621680354945 :: [b]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithM_Sym2 a6989586621680354943 a6989586621680354944 :: TyFun [b] (m ()) -> Type) (a6989586621680354945 :: [b]) = ZipWithM_ a6989586621680354943 a6989586621680354944 a6989586621680354945
type Apply (ZipWithMSym2 a6989586621680354953 a6989586621680354954 :: TyFun [b] (m [c]) -> Type) (a6989586621680354955 :: [b]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithMSym2 a6989586621680354953 a6989586621680354954 :: TyFun [b] (m [c]) -> Type) (a6989586621680354955 :: [b]) = ZipWithM a6989586621680354953 a6989586621680354954 a6989586621680354955
type Apply (LiftA2Sym2 a6989586621679271261 a6989586621679271262 :: TyFun (f b) (f c) -> Type) (a6989586621679271263 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym2 a6989586621679271261 a6989586621679271262 :: TyFun (f b) (f c) -> Type) (a6989586621679271263 :: f b) = LiftA2 a6989586621679271261 a6989586621679271262 a6989586621679271263
type Apply (LiftM2Sym2 a6989586621679271130 a6989586621679271131 :: TyFun (m a2) (m r) -> Type) (a6989586621679271132 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM2Sym2 a6989586621679271130 a6989586621679271131 :: TyFun (m a2) (m r) -> Type) (a6989586621679271132 :: m a2) = LiftM2 a6989586621679271130 a6989586621679271131 a6989586621679271132
type Apply (MzipWithSym2 a6989586621680264769 a6989586621680264770 :: TyFun (m b) (m c) -> Type) (a6989586621680264771 :: m b) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym2 a6989586621680264769 a6989586621680264770 :: TyFun (m b) (m c) -> Type) (a6989586621680264771 :: m b) = MzipWith a6989586621680264769 a6989586621680264770 a6989586621680264771
type Apply (FoldlMSym2 a6989586621679922477 a6989586621679922478 :: TyFun (t a) (m b) -> Type) (a6989586621679922479 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym2 a6989586621679922477 a6989586621679922478 :: TyFun (t a) (m b) -> Type) (a6989586621679922479 :: t a) = FoldlM a6989586621679922477 a6989586621679922478 a6989586621679922479
type Apply (FoldrMSym2 a6989586621679922495 a6989586621679922496 :: TyFun (t a) (m b) -> Type) (a6989586621679922497 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym2 a6989586621679922495 a6989586621679922496 :: TyFun (t a) (m b) -> Type) (a6989586621679922497 :: t a) = FoldrM a6989586621679922495 a6989586621679922496 a6989586621679922497
type Apply (ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949 :: TyFun [c] [d] -> Type) (a6989586621679544950 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949 :: TyFun [c] [d] -> Type) (a6989586621679544950 :: [c]) = ZipWith3 a6989586621679544947 a6989586621679544948 a6989586621679544949 a6989586621679544950
type Apply (Zip4Sym3 a6989586621679656286 a6989586621679656287 a6989586621679656288 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621679656289 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym3 a6989586621679656286 a6989586621679656287 a6989586621679656288 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621679656289 :: [d]) = Zip4 a6989586621679656286 a6989586621679656287 a6989586621679656288 a6989586621679656289
type Apply (LiftA3Sym3 a6989586621679271189 a6989586621679271190 a6989586621679271191 :: TyFun (f c) (f d) -> Type) (a6989586621679271192 :: f c) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym3 a6989586621679271189 a6989586621679271190 a6989586621679271191 :: TyFun (f c) (f d) -> Type) (a6989586621679271192 :: f c) = LiftA3 a6989586621679271189 a6989586621679271190 a6989586621679271191 a6989586621679271192
type Apply (LiftM3Sym3 a6989586621679271100 a6989586621679271101 a6989586621679271102 :: TyFun (m a3) (m r) -> Type) (a6989586621679271103 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym3 a6989586621679271100 a6989586621679271101 a6989586621679271102 :: TyFun (m a3) (m r) -> Type) (a6989586621679271103 :: m a3) = LiftM3 a6989586621679271100 a6989586621679271101 a6989586621679271102 a6989586621679271103
type Apply (ZipWith4Sym4 a6989586621679656166 a6989586621679656167 a6989586621679656168 a6989586621679656169 :: TyFun [d] [e] -> Type) (a6989586621679656170 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym4 a6989586621679656166 a6989586621679656167 a6989586621679656168 a6989586621679656169 :: TyFun [d] [e] -> Type) (a6989586621679656170 :: [d]) = ZipWith4 a6989586621679656166 a6989586621679656167 a6989586621679656168 a6989586621679656169 a6989586621679656170
type Apply (Zip5Sym4 a6989586621679656263 a6989586621679656264 a6989586621679656265 a6989586621679656266 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621679656267 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym4 a6989586621679656263 a6989586621679656264 a6989586621679656265 a6989586621679656266 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621679656267 :: [e]) = Zip5 a6989586621679656263 a6989586621679656264 a6989586621679656265 a6989586621679656266 a6989586621679656267
type Apply (LiftM4Sym4 a6989586621679271061 a6989586621679271062 a6989586621679271063 a6989586621679271064 :: TyFun (m a4) (m r) -> Type) (a6989586621679271065 :: m a4) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym4 a6989586621679271061 a6989586621679271062 a6989586621679271063 a6989586621679271064 :: TyFun (m a4) (m r) -> Type) (a6989586621679271065 :: m a4) = LiftM4 a6989586621679271061 a6989586621679271062 a6989586621679271063 a6989586621679271064 a6989586621679271065
type Apply (ZipWith5Sym5 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 a6989586621679656147 :: TyFun [e] [f] -> Type) (a6989586621679656148 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym5 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 a6989586621679656147 :: TyFun [e] [f] -> Type) (a6989586621679656148 :: [e]) = ZipWith5 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 a6989586621679656147 a6989586621679656148
type Apply (Zip6Sym5 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 a6989586621679656239 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679656240 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym5 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 a6989586621679656239 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679656240 :: [f]) = Zip6 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 a6989586621679656239 a6989586621679656240
type Apply (LiftM5Sym5 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 a6989586621679271017 :: TyFun (m a5) (m r) -> Type) (a6989586621679271018 :: m a5) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym5 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 a6989586621679271017 :: TyFun (m a5) (m r) -> Type) (a6989586621679271018 :: m a5) = LiftM5 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 a6989586621679271017 a6989586621679271018
type Apply (ZipWith6Sym6 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 a6989586621679656121 :: TyFun [f] [g] -> Type) (a6989586621679656122 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym6 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 a6989586621679656121 :: TyFun [f] [g] -> Type) (a6989586621679656122 :: [f]) = ZipWith6 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 a6989586621679656121 a6989586621679656122
type Apply (Zip7Sym6 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 a6989586621679656207 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679656208 :: [g]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym6 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 a6989586621679656207 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679656208 :: [g]) = Zip7 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 a6989586621679656207 a6989586621679656208
type Apply (ZipWith7Sym7 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 a6989586621679656091 :: TyFun [g] [h] -> Type) (a6989586621679656092 :: [g]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym7 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 a6989586621679656091 :: TyFun [g] [h] -> Type) (a6989586621679656092 :: [g]) = ZipWith7 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 a6989586621679656091 a6989586621679656092
type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621680286938 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621680286938 :: NonEmpty a) = (!!@#@$$) a6989586621680286938
type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621680287345 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) (a6989586621680287345 :: NonEmpty a) = Uncons a6989586621680287345
type Apply ((:$$:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621679803713 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply ((:$$:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621679803713 :: ErrorMessage' s) = (:$$:@#@$$) a6989586621679803713
type Apply ((:<>:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621679803710 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply ((:<>:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621679803710 :: ErrorMessage' s) = (:<>:@#@$$) a6989586621679803710
type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621680286965 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621680286965 :: [a]) = IsPrefixOfSym1 a6989586621680286965
type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679544266 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679544266 :: [a]) = (!!@#@$$) a6989586621679544266
type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679545415 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679545415 :: [a]) = IntercalateSym1 a6989586621679545415
type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679656297 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679656297 :: [a]) = StripPrefixSym1 a6989586621679656297
type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545011 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545011 :: [a]) = IsInfixOfSym1 a6989586621679545011
type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545025 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545025 :: [a]) = IsPrefixOfSym1 a6989586621679545025
type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545018 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545018 :: [a]) = IsSuffixOfSym1 a6989586621679545018
type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544612 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544612 :: [a]) = IntersectSym1 a6989586621679544612
type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544203 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544203 :: [a]) = UnionSym1 a6989586621679544203
type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544792 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544792 :: [a]) = (\\@#@$$) a6989586621679544792
type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679154364 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679154364 :: [a]) = (++@#@$$) a6989586621679154364
type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807418 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807418 :: [a]) = ShowListSym1 a6989586621679807418
type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621680286888 :: NonEmpty (a, b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621680286888 :: NonEmpty (a, b)) = Unzip a6989586621680286888
type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621680286929 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621680286929 :: NonEmpty a) = ZipSym1 a6989586621680286929 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type
type Apply (BreakSym1 a6989586621680287110 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287111 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym1 a6989586621680287110 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287111 :: NonEmpty a) = Break a6989586621680287110 a6989586621680287111
type Apply (PartitionSym1 a6989586621680287092 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287093 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym1 a6989586621680287092 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287093 :: NonEmpty a) = Partition a6989586621680287092 a6989586621680287093
type Apply (SpanSym1 a6989586621680287119 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287120 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym1 a6989586621680287119 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287120 :: NonEmpty a) = Span a6989586621680287119 a6989586621680287120
type Apply (SplitAtSym1 a6989586621680287146 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287147 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SplitAtSym1 a6989586621680287146 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621680287147 :: NonEmpty a) = SplitAt a6989586621680287146 a6989586621680287147
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679544929 :: [(a, b)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679544929 :: [(a, b)]) = Unzip a6989586621679544929
type Apply (DeleteFirstsBySym1 a6989586621679544763 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544764 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym1 a6989586621679544763 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544764 :: [a]) = DeleteFirstsBySym2 a6989586621679544763 a6989586621679544764
type Apply (IntersectBySym1 a6989586621679544588 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544589 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym1 a6989586621679544588 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544589 :: [a]) = IntersectBySym2 a6989586621679544588 a6989586621679544589
type Apply (UnionBySym1 a6989586621679544211 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544212 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym1 a6989586621679544211 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544212 :: [a]) = UnionBySym2 a6989586621679544211 a6989586621679544212
type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679544986 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679544986 :: [a]) = ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type
type Apply (ShowListWithSym1 a6989586621679807383 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807384 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym1 a6989586621679807383 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807384 :: [a]) = ShowListWithSym2 a6989586621679807383 a6989586621679807384
type Apply (BreakSym1 a6989586621679544458 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544459 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym1 a6989586621679544458 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544459 :: [a]) = Break a6989586621679544458 a6989586621679544459
type Apply (PartitionSym1 a6989586621679544342 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544343 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (PartitionSym1 a6989586621679544342 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544343 :: [a]) = Partition a6989586621679544342 a6989586621679544343
type Apply (SpanSym1 a6989586621679544497 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544498 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym1 a6989586621679544497 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544498 :: [a]) = Span a6989586621679544497 a6989586621679544498
type Apply (SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544426 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544426 :: [a]) = SplitAt a6989586621679544425 a6989586621679544426
type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679271374 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679271374 :: f a) = (<|>@#@$$) a6989586621679271374
type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679271380 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679271380 :: m a) = MplusSym1 a6989586621679271380
type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679544974 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679544974 :: [a]) = Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type
type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679271255 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679271255 :: f (a ~> b)) = (<*>@#@$$) a6989586621679271255
type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679357509 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679357509 :: f a) = (<&>@#@$$) a6989586621679357509 :: TyFun (a ~> b) (f b) -> Type
type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679357502 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679357502 :: f a) = ($>@#@$$) a6989586621679357502 :: TyFun b (f b) -> Type
type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679271211 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679271211 :: f a) = (<**>@#@$$) a6989586621679271211 :: TyFun (f (a ~> b)) (f b) -> Type
type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679271272 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679271272 :: f a) = (<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type
type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679271267 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679271267 :: f a) = (*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type
type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679270990 :: m (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679270990 :: m (a ~> b)) = ApSym1 a6989586621679270990
type Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) (a6989586621680264774 :: m (a, b)) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) (a6989586621680264774 :: m (a, b)) = Munzip a6989586621680264774
type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679271335 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679271335 :: m a) = (>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type
type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621680264763 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621680264763 :: m a) = MzipSym1 a6989586621680264763 :: TyFun (m b) (m (a, b)) -> Type
type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679271340 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679271340 :: m a) = (>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type
type Apply (ZipWithSym1 a6989586621680286918 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621680286919 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym1 a6989586621680286918 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621680286919 :: NonEmpty a) = ZipWithSym2 a6989586621680286918 a6989586621680286919
type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679656286 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679656286 :: [a]) = Zip4Sym1 a6989586621679656286 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type
type Apply (ZipWithSym1 a6989586621679544962 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679544963 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym1 a6989586621679544962 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679544963 :: [a]) = ZipWithSym2 a6989586621679544962 a6989586621679544963
type Apply (Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679544975 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679544975 :: [b]) = Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type
type Apply (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) (a6989586621680392419 :: f a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Apply (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) (a6989586621680392419 :: f a) = PairSym1 a6989586621680392419 :: TyFun (g a) (Product f g a) -> Type
type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621679922460 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621679922460 :: t a) = For_Sym1 a6989586621679922460 :: TyFun (a ~> f b) (f ()) -> Type
type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680103106 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680103106 :: t a) = ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type
type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621679922440 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621679922440 :: t a) = ForM_Sym1 a6989586621679922440 :: TyFun (a ~> m b) (m ()) -> Type
type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680103095 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680103095 :: t a) = ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type
type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679656263 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679656263 :: [a]) = Zip5Sym1 a6989586621679656263 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type
type Apply (ZipWith3Sym1 a6989586621679544947 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679544948 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym1 a6989586621679544947 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679544948 :: [a]) = ZipWith3Sym2 a6989586621679544947 a6989586621679544948
type Apply (ZipWithM_Sym1 a6989586621680354943 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621680354944 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithM_Sym1 a6989586621680354943 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621680354944 :: [a]) = ZipWithM_Sym2 a6989586621680354943 a6989586621680354944
type Apply (ZipWithMSym1 a6989586621680354953 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621680354954 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithMSym1 a6989586621680354953 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621680354954 :: [a]) = ZipWithMSym2 a6989586621680354953 a6989586621680354954
type Apply (Zip4Sym1 a6989586621679656286 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679656287 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym1 a6989586621679656286 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679656287 :: [b]) = Zip4Sym2 a6989586621679656286 a6989586621679656287 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type
type Apply (LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679271262 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679271262 :: f a) = LiftA2Sym2 a6989586621679271261 a6989586621679271262
type Apply (MzipWithSym1 a6989586621680264769 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621680264770 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym1 a6989586621680264769 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621680264770 :: m a) = MzipWithSym2 a6989586621680264769 a6989586621680264770
type Apply (LiftM2Sym1 a6989586621679271130 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679271131 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM2Sym1 a6989586621679271130 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679271131 :: m a1) = LiftM2Sym2 a6989586621679271130 a6989586621679271131
type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679656235 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679656235 :: [a]) = Zip6Sym1 a6989586621679656235 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type
type Apply (ZipWith4Sym1 a6989586621679656166 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679656167 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym1 a6989586621679656166 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679656167 :: [a]) = ZipWith4Sym2 a6989586621679656166 a6989586621679656167
type Apply (Zip5Sym1 a6989586621679656263 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679656264 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym1 a6989586621679656263 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679656264 :: [b]) = Zip5Sym2 a6989586621679656263 a6989586621679656264 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type
type Apply (ZipWith3Sym2 a6989586621679544947 a6989586621679544948 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679544949 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym2 a6989586621679544947 a6989586621679544948 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679544949 :: [b]) = ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949
type Apply (Zip4Sym2 a6989586621679656286 a6989586621679656287 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679656288 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym2 a6989586621679656286 a6989586621679656287 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679656288 :: [c]) = Zip4Sym3 a6989586621679656286 a6989586621679656287 a6989586621679656288 :: TyFun [d] [(a, b, c, d)] -> Type
type Apply (LiftA3Sym1 a6989586621679271189 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679271190 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym1 a6989586621679271189 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679271190 :: f a) = LiftA3Sym2 a6989586621679271189 a6989586621679271190
type Apply (LiftM3Sym1 a6989586621679271100 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679271101 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym1 a6989586621679271100 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679271101 :: m a1) = LiftM3Sym2 a6989586621679271100 a6989586621679271101
type Apply (MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type) (a6989586621680103084 :: t b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type) (a6989586621680103084 :: t b) = MapAccumL a6989586621680103082 a6989586621680103083 a6989586621680103084
type Apply (MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type) (a6989586621680103074 :: t b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type) (a6989586621680103074 :: t b) = MapAccumR a6989586621680103072 a6989586621680103073 a6989586621680103074
type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679656202 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679656202 :: [a]) = Zip7Sym1 a6989586621679656202 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type
type Apply (ZipWith5Sym1 a6989586621679656143 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679656144 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym1 a6989586621679656143 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679656144 :: [a]) = ZipWith5Sym2 a6989586621679656143 a6989586621679656144
type Apply (Zip6Sym1 a6989586621679656235 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679656236 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym1 a6989586621679656235 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679656236 :: [b]) = Zip6Sym2 a6989586621679656235 a6989586621679656236 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type
type Apply (ZipWith4Sym2 a6989586621679656166 a6989586621679656167 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679656168 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym2 a6989586621679656166 a6989586621679656167 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679656168 :: [b]) = ZipWith4Sym3 a6989586621679656166 a6989586621679656167 a6989586621679656168
type Apply (Zip5Sym2 a6989586621679656263 a6989586621679656264 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679656265 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym2 a6989586621679656263 a6989586621679656264 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679656265 :: [c]) = Zip5Sym3 a6989586621679656263 a6989586621679656264 a6989586621679656265 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type
type Apply (LiftA3Sym2 a6989586621679271189 a6989586621679271190 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679271191 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym2 a6989586621679271189 a6989586621679271190 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679271191 :: f b) = LiftA3Sym3 a6989586621679271189 a6989586621679271190 a6989586621679271191
type Apply (LiftM4Sym1 a6989586621679271061 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679271062 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym1 a6989586621679271061 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679271062 :: m a1) = LiftM4Sym2 a6989586621679271061 a6989586621679271062
type Apply (LiftM3Sym2 a6989586621679271100 a6989586621679271101 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679271102 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym2 a6989586621679271100 a6989586621679271101 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679271102 :: m a2) = LiftM3Sym3 a6989586621679271100 a6989586621679271101 a6989586621679271102
type Apply (ZipWith6Sym1 a6989586621679656116 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679656117 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym1 a6989586621679656116 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679656117 :: [a]) = ZipWith6Sym2 a6989586621679656116 a6989586621679656117
type Apply (Zip7Sym1 a6989586621679656202 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679656203 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym1 a6989586621679656202 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679656203 :: [b]) = Zip7Sym2 a6989586621679656202 a6989586621679656203 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type
type Apply (ZipWith5Sym2 a6989586621679656143 a6989586621679656144 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679656145 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym2 a6989586621679656143 a6989586621679656144 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679656145 :: [b]) = ZipWith5Sym3 a6989586621679656143 a6989586621679656144 a6989586621679656145
type Apply (Zip6Sym2 a6989586621679656235 a6989586621679656236 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679656237 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym2 a6989586621679656235 a6989586621679656236 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679656237 :: [c]) = Zip6Sym3 a6989586621679656235 a6989586621679656236 a6989586621679656237 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type
type Apply (ZipWith4Sym3 a6989586621679656166 a6989586621679656167 a6989586621679656168 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679656169 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym3 a6989586621679656166 a6989586621679656167 a6989586621679656168 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679656169 :: [c]) = ZipWith4Sym4 a6989586621679656166 a6989586621679656167 a6989586621679656168 a6989586621679656169
type Apply (Zip5Sym3 a6989586621679656263 a6989586621679656264 a6989586621679656265 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679656266 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym3 a6989586621679656263 a6989586621679656264 a6989586621679656265 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679656266 :: [d]) = Zip5Sym4 a6989586621679656263 a6989586621679656264 a6989586621679656265 a6989586621679656266 :: TyFun [e] [(a, b, c, d, e)] -> Type
type Apply (LiftM5Sym1 a6989586621679271013 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679271014 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym1 a6989586621679271013 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679271014 :: m a1) = LiftM5Sym2 a6989586621679271013 a6989586621679271014
type Apply (LiftM4Sym2 a6989586621679271061 a6989586621679271062 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679271063 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym2 a6989586621679271061 a6989586621679271062 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679271063 :: m a2) = LiftM4Sym3 a6989586621679271061 a6989586621679271062 a6989586621679271063
type Apply (ZipWith7Sym1 a6989586621679656085 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679656086 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym1 a6989586621679656085 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679656086 :: [a]) = ZipWith7Sym2 a6989586621679656085 a6989586621679656086
type Apply (ZipWith6Sym2 a6989586621679656116 a6989586621679656117 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679656118 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym2 a6989586621679656116 a6989586621679656117 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679656118 :: [b]) = ZipWith6Sym3 a6989586621679656116 a6989586621679656117 a6989586621679656118
type Apply (Zip7Sym2 a6989586621679656202 a6989586621679656203 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679656204 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym2 a6989586621679656202 a6989586621679656203 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679656204 :: [c]) = Zip7Sym3 a6989586621679656202 a6989586621679656203 a6989586621679656204 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type
type Apply (ZipWith5Sym3 a6989586621679656143 a6989586621679656144 a6989586621679656145 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679656146 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym3 a6989586621679656143 a6989586621679656144 a6989586621679656145 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679656146 :: [c]) = ZipWith5Sym4 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146
type Apply (Zip6Sym3 a6989586621679656235 a6989586621679656236 a6989586621679656237 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679656238 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym3 a6989586621679656235 a6989586621679656236 a6989586621679656237 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679656238 :: [d]) = Zip6Sym4 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type
type Apply (LiftM5Sym2 a6989586621679271013 a6989586621679271014 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679271015 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym2 a6989586621679271013 a6989586621679271014 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679271015 :: m a2) = LiftM5Sym3 a6989586621679271013 a6989586621679271014 a6989586621679271015
type Apply (LiftM4Sym3 a6989586621679271061 a6989586621679271062 a6989586621679271063 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679271064 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym3 a6989586621679271061 a6989586621679271062 a6989586621679271063 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679271064 :: m a3) = LiftM4Sym4 a6989586621679271061 a6989586621679271062 a6989586621679271063 a6989586621679271064
type Apply (ZipWith7Sym2 a6989586621679656085 a6989586621679656086 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679656087 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym2 a6989586621679656085 a6989586621679656086 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679656087 :: [b]) = ZipWith7Sym3 a6989586621679656085 a6989586621679656086 a6989586621679656087
type Apply (ZipWith6Sym3 a6989586621679656116 a6989586621679656117 a6989586621679656118 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679656119 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym3 a6989586621679656116 a6989586621679656117 a6989586621679656118 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679656119 :: [c]) = ZipWith6Sym4 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119
type Apply (Zip7Sym3 a6989586621679656202 a6989586621679656203 a6989586621679656204 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679656205 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym3 a6989586621679656202 a6989586621679656203 a6989586621679656204 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679656205 :: [d]) = Zip7Sym4 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type
type Apply (ZipWith5Sym4 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679656147 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym4 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679656147 :: [d]) = ZipWith5Sym5 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 a6989586621679656147
type Apply (Zip6Sym4 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679656239 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym4 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679656239 :: [e]) = Zip6Sym5 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 a6989586621679656239 :: TyFun [f] [(a, b, c, d, e, f)] -> Type
type Apply (LiftM5Sym3 a6989586621679271013 a6989586621679271014 a6989586621679271015 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679271016 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym3 a6989586621679271013 a6989586621679271014 a6989586621679271015 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679271016 :: m a3) = LiftM5Sym4 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016
type Apply (ZipWith7Sym3 a6989586621679656085 a6989586621679656086 a6989586621679656087 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679656088 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym3 a6989586621679656085 a6989586621679656086 a6989586621679656087 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679656088 :: [c]) = ZipWith7Sym4 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088
type Apply (ZipWith6Sym4 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679656120 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym4 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679656120 :: [d]) = ZipWith6Sym5 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120
type Apply (Zip7Sym4 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679656206 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym4 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679656206 :: [e]) = Zip7Sym5 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type
type Apply (LiftM5Sym4 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679271017 :: m a4) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym4 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679271017 :: m a4) = LiftM5Sym5 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 a6989586621679271017
type Apply (ZipWith7Sym4 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679656089 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym4 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679656089 :: [d]) = ZipWith7Sym5 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089
type Apply (ZipWith6Sym5 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679656121 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym5 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679656121 :: [e]) = ZipWith6Sym6 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 a6989586621679656121
type Apply (Zip7Sym5 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679656207 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym5 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679656207 :: [f]) = Zip7Sym6 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 a6989586621679656207 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type
type Apply (ZipWith7Sym5 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679656090 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym5 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679656090 :: [e]) = ZipWith7Sym6 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090
type Apply (ZipWith7Sym6 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679656091 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym6 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679656091 :: [f]) = ZipWith7Sym7 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 a6989586621679656091
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679544912 :: [(a, b, c)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679544912 :: [(a, b, c)]) = Unzip3 a6989586621679544912
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679544893 :: [(a, b, c, d)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679544893 :: [(a, b, c, d)]) = Unzip4 a6989586621679544893
type Apply (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) (a6989586621680331253 :: f a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

type Apply (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) (a6989586621680331253 :: f a) = 'InL a6989586621680331253 :: Sum f g a
type Apply (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) (a6989586621680331255 :: g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

type Apply (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) (a6989586621680331255 :: g a) = 'InR a6989586621680331255 :: Sum f g a
type Apply (PairSym1 a6989586621680392419 :: TyFun (g a) (Product f g a) -> Type) (a6989586621680392420 :: g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Apply (PairSym1 a6989586621680392419 :: TyFun (g a) (Product f g a) -> Type) (a6989586621680392420 :: g a) = 'Pair a6989586621680392419 a6989586621680392420
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679544872 :: [(a, b, c, d, e)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679544872 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679544872
type Apply (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) (a6989586621680345043 :: f (g a)) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

type Apply (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) (a6989586621680345043 :: f (g a)) = 'Compose a6989586621680345043
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679544849 :: [(a, b, c, d, e, f)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679544849 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679544849
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679544824 :: [(a, b, c, d, e, f, g)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679544824 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679544824
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679261595 :: Either a b) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679261595 :: Either a b) = IsLeft a6989586621679261595
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679261592 :: Either a b) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679261592 :: Either a b) = IsRight a6989586621679261592
type Apply (FstSym0 :: TyFun (a, b) a -> Type) (a6989586621679147673 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (FstSym0 :: TyFun (a, b) a -> Type) (a6989586621679147673 :: (a, b)) = Fst a6989586621679147673
type Apply (SndSym0 :: TyFun (a, b) b -> Type) (a6989586621679147669 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (SndSym0 :: TyFun (a, b) b -> Type) (a6989586621679147669 :: (a, b)) = Snd a6989586621679147669
type Apply ((&@#@$$) a6989586621679253960 :: TyFun (a ~> b) b -> Type) (a6989586621679253961 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply ((&@#@$$) a6989586621679253960 :: TyFun (a ~> b) b -> Type) (a6989586621679253961 :: a ~> b) = a6989586621679253960 & a6989586621679253961
type Apply (UncurrySym1 a6989586621679147653 :: TyFun (a, b) c -> Type) (a6989586621679147654 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym1 a6989586621679147653 :: TyFun (a, b) c -> Type) (a6989586621679147654 :: (a, b)) = Uncurry a6989586621679147653 a6989586621679147654
type Apply (Either_Sym2 a6989586621679259290 a6989586621679259291 :: TyFun (Either a b) c -> Type) (a6989586621679259292 :: Either a b) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym2 a6989586621679259290 a6989586621679259291 :: TyFun (Either a b) c -> Type) (a6989586621679259292 :: Either a b) = Either_ a6989586621679259290 a6989586621679259291 a6989586621679259292
type Apply ((<&>@#@$$) a6989586621679357509 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679357510 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$$) a6989586621679357509 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679357510 :: a ~> b) = a6989586621679357509 <&> a6989586621679357510
type Apply ((>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679271336 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679271336 :: a ~> m b) = a6989586621679271335 >>= a6989586621679271336
type Apply (For_Sym1 a6989586621679922460 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621679922461 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym1 a6989586621679922460 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621679922461 :: a ~> f b) = For_ a6989586621679922460 a6989586621679922461
type Apply (ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680103107 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680103107 :: a ~> f b) = For a6989586621680103106 a6989586621680103107
type Apply (ForM_Sym1 a6989586621679922440 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621679922441 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym1 a6989586621679922440 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621679922441 :: a ~> m b) = ForM_ a6989586621679922440 a6989586621679922441
type Apply (ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680103096 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680103096 :: a ~> m b) = ForM a6989586621680103095 a6989586621680103096
type Apply (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621679807347 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621679807347 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621679807346 a6989586621679807347
type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807383 :: a ~> (Symbol ~> Symbol)) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807383 :: a ~> (Symbol ~> Symbol)) = ShowListWithSym1 a6989586621679807383
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286856 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286856 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621680286856
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679544751 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679544751 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621679544751
type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679544731 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679544731 :: a ~> (a ~> Ordering)) = InsertBySym1 a6989586621679544731
type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286992 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286992 :: a ~> (a ~> Bool)) = GroupBy1Sym1 a6989586621680286992
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286869 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286869 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621680286869
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544763 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544763 :: a ~> (a ~> Bool)) = DeleteFirstsBySym1 a6989586621679544763
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544588 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544588 :: a ~> (a ~> Bool)) = IntersectBySym1 a6989586621679544588
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544211 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544211 :: a ~> (a ~> Bool)) = UnionBySym1 a6989586621679544211
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287048 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287048 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621680287048
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679544364 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679544364 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621679544364
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679544231 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679544231 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621679544231
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679544773 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679544773 :: a ~> (a ~> Bool)) = DeleteBySym1 a6989586621679544773
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287198 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287198 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621680287198
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287190 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287190 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621680287190
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545217 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545217 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679545217
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545179 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545179 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679545179
type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679545295 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679545295 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679545295
type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287110 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287110 :: a ~> Bool) = BreakSym1 a6989586621680287110
type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287092 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287092 :: a ~> Bool) = PartitionSym1 a6989586621680287092
type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287119 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287119 :: a ~> Bool) = SpanSym1 a6989586621680287119
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287128 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287128 :: a ~> Bool) = DropWhileSym1 a6989586621680287128
type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287101 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287101 :: a ~> Bool) = FilterSym1 a6989586621680287101
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287137 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287137 :: a ~> Bool) = TakeWhileSym1 a6989586621680287137
type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679154281 :: a ~> Bool) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679154281 :: a ~> Bool) = UntilSym1 a6989586621679154281
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679544640 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679544640 :: a ~> Bool) = FindIndexSym1 a6989586621679544640
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544458 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544458 :: a ~> Bool) = BreakSym1 a6989586621679544458
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544342 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544342 :: a ~> Bool) = PartitionSym1 a6989586621679544342
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544497 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544497 :: a ~> Bool) = SpanSym1 a6989586621679544497
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679544619 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679544619 :: a ~> Bool) = FindIndicesSym1 a6989586621679544619
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544538 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544538 :: a ~> Bool) = DropWhileEndSym1 a6989586621679544538
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544559 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544559 :: a ~> Bool) = DropWhileSym1 a6989586621679544559
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544674 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544674 :: a ~> Bool) = FilterSym1 a6989586621679544674
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544574 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544574 :: a ~> Bool) = TakeWhileSym1 a6989586621679544574
type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621679922335 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621679922335 :: a ~> (a ~> Ordering)) = MaximumBySym1 a6989586621679922335 :: TyFun (t a) a -> Type
type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621679922315 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621679922315 :: a ~> (a ~> Ordering)) = MinimumBySym1 a6989586621679922315 :: TyFun (t a) a -> Type
type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922553 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922553 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type
type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922548 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922548 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287209 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287209 :: a ~> (b ~> b)) = ScanrSym1 a6989586621680287209
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545199 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545199 :: a ~> (b ~> b)) = ScanrSym1 a6989586621679545199
type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679390184 :: a ~> Maybe b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679390184 :: a ~> Maybe b) = MapMaybeSym1 a6989586621679390184
type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287356 :: a ~> (b, Maybe a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287356 :: a ~> (b, Maybe a)) = UnfoldSym1 a6989586621680287356
type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287321 :: a ~> (b, Maybe a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287321 :: a ~> (b, Maybe a)) = UnfoldrSym1 a6989586621680287321
type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621680354827 :: a ~> Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621680354827 :: a ~> Bool) = MfilterSym1 a6989586621680354827 :: TyFun (m a) (m a) -> Type
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621679922286 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621679922286 :: a ~> Bool) = FindSym1 a6989586621679922286 :: TyFun (t a) (Maybe a) -> Type
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922355 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922355 :: a ~> Bool) = AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922364 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922364 :: a ~> Bool) = AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type
type Apply (UntilSym1 a6989586621679154281 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679154282 :: a ~> a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym1 a6989586621679154281 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679154282 :: a ~> a) = UntilSym2 a6989586621679154281 a6989586621679154282
type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286976 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286976 :: a ~> b) = GroupAllWith1Sym1 a6989586621680286976
type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286985 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286985 :: a ~> b) = GroupWith1Sym1 a6989586621680286985
type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621680287251 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621680287251 :: a ~> b) = MapSym1 a6989586621680287251
type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287030 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287030 :: a ~> b) = GroupAllWithSym1 a6989586621680287030
type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287039 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287039 :: a ~> b) = GroupWithSym1 a6989586621680287039
type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679154373 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679154373 :: a ~> b) = MapSym1 a6989586621679154373
type Apply ((@@@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) # 
Instance details

Defined in Data.Singletons

type Apply ((@@@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) = (@@@#@$$) f
type Apply (ApplySym0 :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) # 
Instance details

Defined in Data.Singletons

type Apply (ApplySym0 :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) = ApplySym1 f
type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154299 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154299 :: a ~> b) = ($!@#@$$) a6989586621679154299
type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154308 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154308 :: a ~> b) = ($@#@$$) a6989586621679154308
type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621680355005 :: a ~> m Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621680355005 :: a ~> m Bool) = FilterMSym1 a6989586621680355005
type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286847 :: a ~> o) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286847 :: a ~> o) = SortWithSym1 a6989586621680286847
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287221 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287221 :: b ~> (a ~> b)) = ScanlSym1 a6989586621680287221
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545226 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545226 :: b ~> (a ~> b)) = ScanlSym1 a6989586621679545226
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679545055 :: b ~> Maybe (a, b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679545055 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679545055
type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679189957 :: b ~> a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679189957 :: b ~> a) = ComparingSym1 a6989586621679189957
type Apply (SwapSym0 :: TyFun (a, b) (b, a) -> Type) (a6989586621679147647 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (SwapSym0 :: TyFun (a, b) (b, a) -> Type) (a6989586621679147647 :: (a, b)) = Swap a6989586621679147647
type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679147661 :: (a, b) ~> c) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679147661 :: (a, b) ~> c) = CurrySym1 a6989586621679147661
type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922528 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922528 :: a ~> (b ~> b)) = Foldr'Sym1 a6989586621679922528 :: TyFun b (t a ~> b) -> Type
type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922521 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922521 :: a ~> (b ~> b)) = FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621680286918 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621680286918 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621680286918
type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679147653 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679147653 :: a ~> (b ~> c)) = UncurrySym1 a6989586621679147653
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679544962 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679544962 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621679544962
type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679154327 :: a ~> (b ~> c)) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679154327 :: a ~> (b ~> c)) = FlipSym1 a6989586621679154327
type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621679922383 :: a ~> [b]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621679922383 :: a ~> [b]) = ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type
type Apply (Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679387994 :: a ~> b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679387994 :: a ~> b) = Maybe_Sym2 a6989586621679387993 a6989586621679387994
type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271227 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271227 :: a ~> b) = FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type
type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271200 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271200 :: a ~> b) = LiftASym1 a6989586621679271200 :: TyFun (f a) (f b) -> Type
type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679357520 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679357520 :: a ~> b) = (<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type
type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621680354845 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621680354845 :: a ~> b) = (<$!>@#@$$) a6989586621680354845 :: TyFun (m a) (m b) -> Type
type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680103058 :: a ~> b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680103058 :: a ~> b) = FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type
type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679259290 :: a ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679259290 :: a ~> c) = Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type
type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621679922515 :: a ~> m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621679922515 :: a ~> m) = FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type
type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680103039 :: a ~> m) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680103039 :: a ~> m) = FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type
type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679271176 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679271176 :: a ~> m b) = (=<<@#@$$) a6989586621679271176
type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679271151 :: a1 ~> r) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679271151 :: a1 ~> r) = LiftMSym1 a6989586621679271151 :: TyFun (m a1) (m r) -> Type
type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922542 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922542 :: b ~> (a ~> b)) = Foldl'Sym1 a6989586621679922542 :: TyFun b (t a ~> b) -> Type
type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922535 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922535 :: b ~> (a ~> b)) = FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type
type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679253973 :: b ~> (b ~> c)) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679253973 :: b ~> (b ~> c)) = OnSym1 a6989586621679253973 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type
type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679154339 :: b ~> c) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679154339 :: b ~> c) = (.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type
type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679544947 :: a ~> (b ~> (c ~> d))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679544947 :: a ~> (b ~> (c ~> d))) = ZipWith3Sym1 a6989586621679544947
type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103082 :: a ~> (b ~> (a, c))) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103082 :: a ~> (b ~> (a, c))) = MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type
type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103072 :: a ~> (b ~> (a, c))) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103072 :: a ~> (b ~> (a, c))) = MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type
type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679271261 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679271261 :: a ~> (b ~> c)) = LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type
type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621680264769 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621680264769 :: a ~> (b ~> c)) = MzipWithSym1 a6989586621680264769 :: TyFun (m a) (m b ~> m c) -> Type
type Apply (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621679922495 :: a ~> (b ~> m b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621679922495 :: a ~> (b ~> m b)) = FoldrMSym1 a6989586621679922495 :: TyFun b (t a ~> m b) -> Type
type Apply (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) (a6989586621680354943 :: a ~> (b ~> m c)) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) (a6989586621680354943 :: a ~> (b ~> m c)) = ZipWithM_Sym1 a6989586621680354943
type Apply (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) (a6989586621680354953 :: a ~> (b ~> m c)) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) (a6989586621680354953 :: a ~> (b ~> m c)) = ZipWithMSym1 a6989586621680354953
type Apply (OnSym1 a6989586621679253973 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679253974 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym1 a6989586621679253973 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679253974 :: a ~> b) = OnSym2 a6989586621679253973 a6989586621679253974
type Apply ((.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679154340 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679154340 :: a ~> b) = a6989586621679154339 .@#@$$$ a6989586621679154340
type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621679922469 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621679922469 :: a ~> f b) = Traverse_Sym1 a6989586621679922469 :: TyFun (t a) (f ()) -> Type
type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680096860 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680096860 :: a ~> f b) = TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type
type Apply (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) (a6989586621680354962 :: a ~> m (b, c)) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) (a6989586621680354962 :: a ~> m (b, c)) = MapAndUnzipMSym1 a6989586621680354962
type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621680354988 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621680354988 :: a ~> m b) = (>=>@#@$$) a6989586621680354988 :: TyFun (b ~> m c) (a ~> m c) -> Type
type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621679922449 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621679922449 :: a ~> m b) = MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type
type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680096868 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680096868 :: a ~> m b) = MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type
type Apply (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) (a6989586621679271130 :: a1 ~> (a2 ~> r)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) (a6989586621679271130 :: a1 ~> (a2 ~> r)) = LiftM2Sym1 a6989586621679271130 :: TyFun (m a1) (m a2 ~> m r) -> Type
type Apply (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621679922477 :: b ~> (a ~> m b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621679922477 :: b ~> (a ~> m b)) = FoldlMSym1 a6989586621679922477 :: TyFun b (t a ~> m b) -> Type
type Apply (Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679259291 :: b ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679259291 :: b ~> c) = Either_Sym2 a6989586621679259290 a6989586621679259291
type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621680354976 :: b ~> m c) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621680354976 :: b ~> m c) = (<=<@#@$$) a6989586621680354976 :: TyFun (a ~> m b) (a ~> m c) -> Type
type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679656166 :: a ~> (b ~> (c ~> (d ~> e)))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679656166 :: a ~> (b ~> (c ~> (d ~> e)))) = ZipWith4Sym1 a6989586621679656166
type Apply (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) (a6989586621679271189 :: a ~> (b ~> (c ~> d))) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) (a6989586621679271189 :: a ~> (b ~> (c ~> d))) = LiftA3Sym1 a6989586621679271189 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type
type Apply ((<=<@#@$$) a6989586621680354976 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621680354977 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<=<@#@$$) a6989586621680354976 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621680354977 :: a ~> m b) = a6989586621680354976 <=<@#@$$$ a6989586621680354977
type Apply (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) (a6989586621679271100 :: a1 ~> (a2 ~> (a3 ~> r))) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) (a6989586621679271100 :: a1 ~> (a2 ~> (a3 ~> r))) = LiftM3Sym1 a6989586621679271100 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type
type Apply ((>=>@#@$$) a6989586621680354988 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621680354989 :: b ~> m c) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((>=>@#@$$) a6989586621680354988 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621680354989 :: b ~> m c) = a6989586621680354988 >=>@#@$$$ a6989586621680354989
type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679656143 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679656143 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) = ZipWith5Sym1 a6989586621679656143
type Apply (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) (a6989586621679271061 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) (a6989586621679271061 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) = LiftM4Sym1 a6989586621679271061 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type
type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621679656116 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621679656116 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) = ZipWith6Sym1 a6989586621679656116
type Apply (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) (a6989586621679271013 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) (a6989586621679271013 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) = LiftM5Sym1 a6989586621679271013 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type
type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621679656085 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621679656085 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) = ZipWith7Sym1 a6989586621679656085
type Apply (GetConstSym0 :: TyFun (Const a b) a -> Type) (a6989586621680067844 :: Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Apply (GetConstSym0 :: TyFun (Const a b) a -> Type) (a6989586621680067844 :: Const a b) = GetConst a6989586621680067844
type Apply (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) (a6989586621680345046 :: Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

type Apply (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) (a6989586621680345046 :: Compose f g a) = GetCompose a6989586621680345046

data ApplySym0 (a1 :: TyFun (a ~> b) (a ~> b)) #

Instances

Instances details
type Apply (ApplySym0 :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) # 
Instance details

Defined in Data.Singletons

type Apply (ApplySym0 :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) = ApplySym1 f

data ApplySym1 (a1 :: a ~> b) (b1 :: TyFun a b) #

Instances

Instances details
type Apply (ApplySym1 f :: TyFun k1 k2 -> Type) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply (ApplySym1 f :: TyFun k1 k2 -> Type) (x :: k1) = Apply f x

type ApplySym2 (f :: a ~> b) (x :: a) = Apply f x #

type family ApplyTyCon :: (k1 -> k2) -> TyFun k1 unmatchable_fun -> Type where ... #

Equations

ApplyTyCon = ApplyTyConAux2 :: (k1 -> k2 -> k3) -> TyFun k1 unmatchable_fun -> Type 
ApplyTyCon = ApplyTyConAux1 :: (k1 -> k2) -> TyFun k1 k2 -> Type 

data ApplyTyConAux1 (a :: k1 -> k2) (b :: TyFun k1 k2) #

Instances

Instances details
type Apply (ApplyTyConAux1 f :: TyFun k1 k2 -> Type) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply (ApplyTyConAux1 f :: TyFun k1 k2 -> Type) (x :: k1) = f x

data ApplyTyConAux2 (a :: k1 -> k2 -> k3) (b :: TyFun k1 unmatchable_fun) #

Instances

Instances details
type Apply (ApplyTyConAux2 f :: TyFun k4 k7 -> Type) (x :: k4) # 
Instance details

Defined in Data.Singletons

type Apply (ApplyTyConAux2 f :: TyFun k4 k7 -> Type) (x :: k4) = TyCon (f x)

type family Demote k = (r :: Type) | r -> k #

Instances

Instances details
type Demote Void Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote All = All
type Demote Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote Any = Any
type Demote Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote PErrorMessage Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Demote Natural Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Demote () Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote () = ()
type Demote Bool Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote Char Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Demote Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Demote (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (First a) = First (Demote a)
type Demote (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Last a) = Last (Demote a)
type Demote (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Max a) = Max (Demote a)
type Demote (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Min a) = Min (Demote a)
type Demote (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (Identity a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Demote (First a) = First (Demote a)
type Demote (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Demote (Last a) = Last (Demote a)
type Demote (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Demote (Down a) = Down (Demote a)
type Demote (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Dual a) = Dual (Demote a)
type Demote (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Product a) = Product (Demote a)
type Demote (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Sum a) = Sum (Demote a)
type Demote (Maybe a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (Maybe a) = Maybe (Demote a)
type Demote (TYPE rep) Source # 
Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

type Demote (TYPE rep) = SomeTypeRepTYPE rep
type Demote [a] Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote [a] = [Demote a]
type Demote (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Demote (Arg a b) = Arg (Demote a) (Demote b)
type Demote (Either a b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (Either a b) = Either (Demote a) (Demote b)
type Demote (Proxy t) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Demote (Proxy t) = Proxy t
type Demote (WrappedSing a) # 
Instance details

Defined in Data.Singletons

type Demote (k1 ~> k2) # 
Instance details

Defined in Data.Singletons

type Demote (k1 ~> k2) = Demote k1 -> Demote k2
type Demote (a, b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b) = (Demote a, Demote b)
type Demote (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Demote (Const a b) = Const (Demote a) b
type Demote (a, b, c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c) = (Demote a, Demote b, Demote c)
type Demote (a, b, c, d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c, d) = (Demote a, Demote b, Demote c, Demote d)
type Demote (a, b, c, d, e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c, d, e) = (Demote a, Demote b, Demote c, Demote d, Demote e)
type Demote (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c, d, e, f) = (Demote a, Demote b, Demote c, Demote d, Demote e, Demote f)
type Demote (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c, d, e, f, g) = (Demote a, Demote b, Demote c, Demote d, Demote e, Demote f, Demote g)

data DemoteSym0 (a :: TyFun Type Type) #

Instances

Instances details
type Apply DemoteSym0 (x :: Type) # 
Instance details

Defined in Data.Singletons

type Apply DemoteSym0 (x :: Type) = Demote x

type DemoteSym1 x = Demote x #

type KindOf (a :: k) = k #

data KindOfSym0 (a :: TyFun k Type) #

Instances

Instances details
type Apply (KindOfSym0 :: TyFun k Type -> Type) (x :: k) # 
Instance details

Defined in Data.Singletons

type Apply (KindOfSym0 :: TyFun k Type -> Type) (x :: k) = KindOf x

type KindOfSym1 (x :: k) = KindOf x #

newtype SLambda (f :: k1 ~> k2) #

Constructors

SLambda 

Fields

newtype SWrappedSing (a1 :: WrappedSing a) where #

Constructors

SWrapSing 

Fields

type SameKind (a :: k) (b :: k) = () #

data SameKindSym0 (a :: TyFun k (k ~> Constraint)) #

Instances

Instances details
type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (x :: k) # 
Instance details

Defined in Data.Singletons

type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (x :: k) = SameKindSym1 x

data SameKindSym1 (a :: k) (b :: TyFun k Constraint) #

Instances

Instances details
type Apply (SameKindSym1 x :: TyFun k Constraint -> Type) (y :: k) # 
Instance details

Defined in Data.Singletons

type Apply (SameKindSym1 x :: TyFun k Constraint -> Type) (y :: k) = SameKind x y

type SameKindSym2 (x :: k) (y :: k) = SameKind x y #

type family Sing :: k -> Type #

Instances

Instances details
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple0
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SBool
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SChar
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SSymbol
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SMax :: Max a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SMin :: Min a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SNonEmpty :: NonEmpty a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SIdentity :: Identity a -> Type
type Sing Source # 
Instance details

Defined in Data.Monoid.Singletons

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Monoid.Singletons

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Ord.Singletons

type Sing = SDown :: Down a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SDual :: Dual a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SProduct :: Product a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SSum :: Sum a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SMaybe :: Maybe a -> Type
type Sing Source #

A choice of singleton for the kind TYPE rep (for some RuntimeRep rep), an instantiation of which is the famous kind Type.

Conceivably, one could generalize this instance to `Sing @k` for any kind k, and remove all other Sing instances. We don't adopt this design, however, since it is far more convenient in practice to work with explicit singleton values than TypeReps (for instance, TypeReps are more difficult to pattern match on, and require extra runtime checks).

We cannot produce explicit singleton values for everything in TYPE rep, however, since it is an open kind, so we reach for TypeRep in this one particular case.

Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

type Sing = TypeRep :: TYPE rep -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SList :: [a] -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Sing = SArg :: Arg a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SEither :: Either a b -> Type
type Sing Source # 
Instance details

Defined in Data.Proxy.Singletons

type Sing = SProxy :: Proxy t -> Type
type Sing # 
Instance details

Defined in Data.Singletons

type Sing # 
Instance details

Defined in Data.Singletons

type Sing = SLambda :: (k1 ~> k2) -> Type
type Sing # 
Instance details

Defined in Data.Singletons.Sigma

type Sing = SSigma :: Sigma s t -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple2 :: (a, b) -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Sing = SConst :: Const a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple3 :: (a, b, c) -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Sing = SProduct :: Product f g a -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

type Sing = SSum :: Sum f g a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple4 :: (a, b, c, d) -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

type Sing = SCompose :: Compose f g a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple5 :: (a, b, c, d, e) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple6 :: (a, b, c, d, e, f) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple7 :: (a, b, c, d, e, f, g) -> Type

type SingFunction1 (f :: a1 ~> b) = forall (t :: a1). Sing t -> Sing (f @@ t) #

type SingFunction2 (f :: a1 ~> (a2 ~> b)) = forall (t1 :: a1) (t2 :: a2). Sing t1 -> Sing t2 -> Sing ((f @@ t1) @@ t2) #

type SingFunction3 (f :: a1 ~> (a2 ~> (a3 ~> b))) = forall (t1 :: a1) (t2 :: a2) (t3 :: a3). Sing t1 -> Sing t2 -> Sing t3 -> Sing (((f @@ t1) @@ t2) @@ t3) #

type SingFunction4 (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> b)))) = forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing ((((f @@ t1) @@ t2) @@ t3) @@ t4) #

type SingFunction5 (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> b))))) = forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing (((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) #

type SingFunction6 (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> b)))))) = forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing ((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) #

type SingFunction7 (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> b))))))) = forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6) (t7 :: a7). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing (((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7) #

type SingFunction8 (f :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> (a6 ~> (a7 ~> (a8 ~> b)))))))) = forall (t1 :: a1) (t2 :: a2) (t3 :: a3) (t4 :: a4) (t5 :: a5) (t6 :: a6) (t7 :: a7) (t8 :: a8). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing t5 -> Sing t6 -> Sing t7 -> Sing t8 -> Sing ((((((((f @@ t1) @@ t2) @@ t3) @@ t4) @@ t5) @@ t6) @@ t7) @@ t8) #

class SingI (a :: k) where #

Methods

sing :: Sing a #

Instances

Instances details
KnownNat n => SingI (n :: Nat) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing n #

SingI 'EQ Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing 'EQ #

SingI 'GT Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing 'GT #

SingI 'LT Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing 'LT #

SingI '() Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing '() #

SingI 'False Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing 'False #

SingI 'True Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing 'True #

KnownChar c => SingI (c :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing c #

KnownSymbol n => SingI (n :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing n #

SingI n => SingI ('All n :: All) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('All n) #

SingI n => SingI ('Any n :: Any) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('Any n) #

SingI t => SingI ('Text t :: ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ('Text t) #

(SingI e1, SingI e2) => SingI (e1 ':$$: e2 :: ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing (e1 ':$$: e2) #

(SingI e1, SingI e2) => SingI (e1 ':<>: e2 :: ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing (e1 ':<>: e2) #

SingI ty => SingI ('ShowType ty :: ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ('ShowType ty :: ErrorMessage' Symbol) #

Typeable a => SingI (a :: TYPE rep) Source # 
Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

Methods

sing :: Sing a #

SingI ('Nothing :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ('Nothing :: Maybe a) #

SingI ('[] :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ('[] :: [a]) #

SingI n => SingI ('First n :: First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('First n) #

SingI n => SingI ('Last n :: Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('Last n) #

SingI n => SingI ('Max n :: Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('Max n) #

SingI n => SingI ('Min n :: Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('Min n) #

SingI n => SingI ('WrapMonoid n :: WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('WrapMonoid n) #

SingI n => SingI ('Identity n :: Identity a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ('Identity n) #

SingI n => SingI ('First n :: First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing ('First n) #

SingI n => SingI ('Last n :: Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing ('Last n) #

SingI n => SingI ('Down n :: Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ('Down n) #

SingI n => SingI ('Dual n :: Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('Dual n) #

SingI n => SingI ('Product n :: Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('Product n) #

SingI n => SingI ('Sum n :: Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing ('Sum n) #

SingI n => SingI ('Just n :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ('Just n) #

(SingI n1, SingI n2) => SingI (n1 ':| n2 :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (n1 ':| n2) #

(SingI n1, SingI n2) => SingI (n1 ': n2 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (n1 ': n2) #

SingI XorSym0 Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing XorSym0 #

SingI GetAllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing GetAllSym0 #

SingI GetAnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing GetAnySym0 #

SingI AllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing AllSym0 #

SingI AnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing AnySym0 #

SingI ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI UnlinesSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI UnwordsSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowCommaSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI DivSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing DivSym0 #

SingI ModSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing ModSym0 #

SingI (^@#@$) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing (^@#@$) #

SingI Log2Sym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing Log2Sym0 #

SingI NatToCharSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingI (&&@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (&&@#@$) #

SingI (||@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (||@#@$) #

SingI NotSym0 Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing NotSym0 #

SingI ConsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingI CharToNatSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingI UnconsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingI (GetFirstSym0 :: TyFun (First a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetFirstSym0 :: TyFun (First a) a -> Type) #

SingI (GetLastSym0 :: TyFun (Last a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetLastSym0 :: TyFun (Last a) a -> Type) #

SingI (GetMaxSym0 :: TyFun (Max a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetMaxSym0 :: TyFun (Max a) a -> Type) #

SingI (GetMinSym0 :: TyFun (Min a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetMinSym0 :: TyFun (Min a) a -> Type) #

SingI (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SingI (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SEq a => SingI (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) #

SEq a => SingI (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) #

SingI (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) #

SOrd a => SingI (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) #

SingI ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) #

SingI (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) #

SingI (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) #

SingI (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) #

SingI (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) #

SingI (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) #

SingI (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (HeadSym0 :: TyFun (NonEmpty a) a -> Type) #

SingI (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (LastSym0 :: TyFun (NonEmpty a) a -> Type) #

SSemigroup a => SingI (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) #

SingI (AbsurdSym0 :: TyFun Void a -> Type) Source # 
Instance details

Defined in Data.Void.Singletons

Methods

sing :: Sing (AbsurdSym0 :: TyFun Void a -> Type) #

SingI (RunIdentitySym0 :: TyFun (Identity a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (RunIdentitySym0 :: TyFun (Identity a) a -> Type) #

SingI (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) #

SingI (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) #

SingI (GetDownSym0 :: TyFun (Down a) a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (GetDownSym0 :: TyFun (Down a) a -> Type) #

SingI (GetDualSym0 :: TyFun (Dual a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetDualSym0 :: TyFun (Dual a) a -> Type) #

SingI (GetProductSym0 :: TyFun (Product a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetProductSym0 :: TyFun (Product a) a -> Type) #

SingI (GetSumSym0 :: TyFun (Sum a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetSumSym0 :: TyFun (Sum a) a -> Type) #

SingI d => SingI (ShowParenSym1 d :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym1 d) #

SingI (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) #

SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) #

SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) #

SingI (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) #

SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) #

SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) #

SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) #

SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) #

SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) #

SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) #

SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) #

SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) #

SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) #

SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) #

SingI (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) #

SingI (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) #

SingI (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) #

SingI (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) #

SingI (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) #

SingI (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) #

SingI (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) #

SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) #

SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) #

SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) #

SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) #

SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) #

SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SingI ((:$$:@#@$) :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol ~> ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI ((:<>:@#@$) :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol ~> ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) #

SingI (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) #

SingI (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) #

SingI (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) #

SingI (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) #

SingI (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) #

SShow a => SingI (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SingI (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) #

SEnum a => SingI (ToEnumSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (ToEnumSym0 :: TyFun Natural a -> Type) #

SNum a => SingI (FromIntegerSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SingI (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) #

SingI (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) #

SingI (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) #

SingI (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) #

SingI (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) #

SingI (FromJustSym0 :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromJustSym0 :: TyFun (Maybe a) a -> Type) #

SApplicative f => SingI (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) #

SApplicative f => SingI (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) #

SAlternative f => SingI (GuardSym0 :: TyFun Bool (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (GuardSym0 :: TyFun Bool (f ()) -> Type) #

SingI (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) #

SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) #

SingI (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) #

SingI (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) #

SingI (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) #

SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) #

SingI ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) #

SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) #

SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) #

SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) #

SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) #

SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) #

SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) #

SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) #

SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) #

SShow a => SingI (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) #

SingI (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) #

SingI (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) #

SEq a => SingI (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) #

SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (GroupSym0 :: TyFun [a] [[a]] -> Type) #

SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InitsSym0 :: TyFun [a] [[a]] -> Type) #

SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (PermutationsSym0 :: TyFun [a] [[a]] -> Type) #

SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) #

SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TailsSym0 :: TyFun [a] [[a]] -> Type) #

SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InitSym0 :: TyFun [a] [a] -> Type) #

SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (NubSym0 :: TyFun [a] [a] -> Type) #

SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReverseSym0 :: TyFun [a] [a] -> Type) #

SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SortSym0 :: TyFun [a] [a] -> Type) #

SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TailSym0 :: TyFun [a] [a] -> Type) #

SingI (HeadSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (HeadSym0 :: TyFun [a] a -> Type) #

SingI (LastSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LastSym0 :: TyFun [a] a -> Type) #

SMonoid a => SingI (MconcatSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MconcatSym0 :: TyFun [a] a -> Type) #

SingI (TextSym0 :: TyFun Symbol (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI d => SingI (ShowCharSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowCharSym1 d) #

SingI d => SingI (ShowStringSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowStringSym1 d) #

SIsString a => SingI (FromStringSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in Data.String.Singletons

Methods

sing :: Sing (FromStringSym0 :: TyFun Symbol a -> Type) #

SingI (ErrorSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing (ErrorSym0 :: TyFun Symbol a -> Type) #

SingI (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SingI (FirstSym0 :: TyFun a (First a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (FirstSym0 :: TyFun a (First a) -> Type) #

SingI (LastSym0 :: TyFun a (Last a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (LastSym0 :: TyFun a (Last a) -> Type) #

SingI (MaxSym0 :: TyFun a (Max a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (MaxSym0 :: TyFun a (Max a) -> Type) #

SingI (MinSym0 :: TyFun a (Min a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (MinSym0 :: TyFun a (Min a) -> Type) #

SingI (IdentitySym0 :: TyFun a (Identity a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (IdentitySym0 :: TyFun a (Identity a) -> Type) #

SingI (DownSym0 :: TyFun a (Down a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (DownSym0 :: TyFun a (Down a) -> Type) #

SingI (DualSym0 :: TyFun a (Dual a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (DualSym0 :: TyFun a (Dual a) -> Type) #

SingI (ProductSym0 :: TyFun a (Product a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (ProductSym0 :: TyFun a (Product a) -> Type) #

SingI (SumSym0 :: TyFun a (Sum a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (SumSym0 :: TyFun a (Sum a) -> Type) #

SingI ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) #

SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) #

SingI ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) #

SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) #

SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) #

SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) #

SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) #

SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) #

SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) #

SShow a => SingI (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) #

SOrd a => SingI (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) #

SingI (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) #

SEnum a => SingI (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) #

SEq a => SingI ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SEq a => SingI ((==@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((==@#@$) :: TyFun a (a ~> Bool) -> Type) #

SOrd a => SingI ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SOrd a => SingI ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<@#@$) :: TyFun a (a ~> Bool) -> Type) #

SOrd a => SingI ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SOrd a => SingI ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>@#@$) :: TyFun a (a ~> Bool) -> Type) #

SEnum a => SingI (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) #

SMonoid a => SingI (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MappendSym0 :: TyFun a (a ~> a) -> Type) #

SOrd a => SingI (MaxSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MaxSym0 :: TyFun a (a ~> a) -> Type) #

SOrd a => SingI (MinSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MinSym0 :: TyFun a (a ~> a) -> Type) #

SSemigroup a => SingI ((<>@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing ((<>@#@$) :: TyFun a (a ~> a) -> Type) #

SingI (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) #

SNum a => SingI ((*@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((*@#@$) :: TyFun a (a ~> a) -> Type) #

SNum a => SingI ((+@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((+@#@$) :: TyFun a (a ~> a) -> Type) #

SNum a => SingI ((-@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((-@#@$) :: TyFun a (a ~> a) -> Type) #

SNum a => SingI (SubtractSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SubtractSym0 :: TyFun a (a ~> a) -> Type) #

SEnum a => SingI (FromEnumSym0 :: TyFun a Natural -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (FromEnumSym0 :: TyFun a Natural -> Type) #

SingI (JustSym0 :: TyFun a (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (JustSym0 :: TyFun a (Maybe a) -> Type) #

SShow a => SingI (Show_Sym0 :: TyFun a Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (Show_Sym0 :: TyFun a Symbol -> Type) #

SEnum a => SingI (PredSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (PredSym0 :: TyFun a a -> Type) #

SEnum a => SingI (SuccSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (SuccSym0 :: TyFun a a -> Type) #

SingI (IdSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (IdSym0 :: TyFun a a -> Type) #

SNum a => SingI (AbsSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (AbsSym0 :: TyFun a a -> Type) #

SNum a => SingI (NegateSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (NegateSym0 :: TyFun a a -> Type) #

SNum a => SingI (SignumSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SignumSym0 :: TyFun a a -> Type) #

SingI (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) #

SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AndSym0 :: TyFun (t Bool) Bool -> Type) #

SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (OrSym0 :: TyFun (t Bool) Bool -> Type) #

SingI (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI ((<=?@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SingI x => SingI (DivSym1 x :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing (DivSym1 x) #

SingI x => SingI (ModSym1 x :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing (ModSym1 x) #

SingI x => SingI ((^@#@$$) x :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing ((^@#@$$) x) #

SingI (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) #

SingI x => SingI ((&&@#@$$) x :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing ((&&@#@$$) x) #

SingI x => SingI ((||@#@$$) x :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing ((||@#@$$) x) #

SingI x => SingI (ConsSymbolSym1 x :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing (ConsSymbolSym1 x) #

SingI ('Proxy :: Proxy t) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sing :: Sing ('Proxy :: Proxy t) #

SingI (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) #

SingI d => SingI (GroupBy1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBy1Sym1 d) #

SingI d => SingI ((<|@#@$$) d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((<|@#@$$) d) #

SingI d => SingI (ConsSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ConsSym1 d) #

SingI d => SingI (IntersperseSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IntersperseSym1 d) #

SingI d => SingI (NubBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NubBySym1 d) #

SingI d => SingI (Scanl1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanl1Sym1 d) #

SingI d => SingI (Scanr1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanr1Sym1 d) #

SingI d => SingI (SortBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortBySym1 d) #

SingI (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) #

SingI d => SingI (BreakSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (BreakSym1 d) #

SingI d => SingI (PartitionSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (PartitionSym1 d) #

SingI d => SingI (SpanSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SpanSym1 d) #

SingI d => SingI (SplitAtSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SplitAtSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) #

(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IsPrefixOfSym1 d) #

SingI d => SingI (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) #

SingI d => SingI (DropWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropWhileSym1 d) #

SingI d => SingI (FilterSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (FilterSym1 d) #

SingI d => SingI (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) #

SingI d => SingI (TakeWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeWhileSym1 d) #

SingI (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) #

SingI (IsRightSym0 :: TyFun (Either a b) Bool -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (IsRightSym0 :: TyFun (Either a b) Bool -> Type) #

SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) #

SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) #

SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) #

SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) #

SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) #

SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) #

SingI (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) #

SingI (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) #

SingI (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) #

SMonadPlus m => SingI (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) #

SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) #

SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) #

SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) #

SingI d => SingI (UntilSym1 d :: TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym1 d) #

SOrd b => SingI (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) #

SEq b => SingI (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) #

SingI (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) #

SOrd b => SingI (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) #

SEq b => SingI (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) #

SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) #

SingI (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) #

SingI (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) #

SApplicative m => SingI (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) #

SOrd o => SingI (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) #

SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) #

SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) #

SOrd a => SingI (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) #

SingI x => SingI ((:$$:@#@$$) x :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ((:$$:@#@$$) x) #

SingI x => SingI ((:<>:@#@$$) x :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ((:<>:@#@$$) x) #

SApplicative m => SingI (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) #

SApplicative m => SingI (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) #

SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((!!@#@$$) d) #

SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((!!@#@$$) d) #

SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromMaybeSym1 d) #

SingI (SwapSym0 :: TyFun (a, b) (b, a) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (SwapSym0 :: TyFun (a, b) (b, a) -> Type) #

SingI (FstSym0 :: TyFun (a, b) a -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (FstSym0 :: TyFun (a, b) a -> Type) #

SingI (SndSym0 :: TyFun (a, b) b -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (SndSym0 :: TyFun (a, b) b -> Type) #

SingI (LeftsSym0 :: TyFun [Either a b] [a] -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (LeftsSym0 :: TyFun [Either a b] [a] -> Type) #

SingI (RightsSym0 :: TyFun [Either a b] [b] -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (RightsSym0 :: TyFun [Either a b] [b] -> Type) #

SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) #

SMonadFail m => SingI (FailSym0 :: TyFun [Char] (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sing :: Sing (FailSym0 :: TyFun [Char] (m a) -> Type) #

SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntercalateSym1 d) #

(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InsertSym1 d) #

SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:|@#@$$) d) #

SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectBySym1 d) #

SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionBySym1 d) #

SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) #

SingI d => SingI (ShowListWithSym1 d :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym1 d) #

(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndexSym1 d) #

SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndexSym1 d) #

SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (BreakSym1 d) #

SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (PartitionSym1 d) #

SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SpanSym1 d) #

SingI d => SingI (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) #

(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsInfixOfSym1 d) #

(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsPrefixOfSym1 d) #

(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsSuffixOfSym1 d) #

SingI d => SingI (GroupBySym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBySym1 d) #

(SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndicesSym1 d) #

SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndicesSym1 d) #

SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (GroupBySym1 d) #

(SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteSym1 d) #

SingI d => SingI (DropSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropSym1 d :: TyFun [a] [a] -> Type) #

SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileEndSym1 d) #

SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileSym1 d) #

SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FilterSym1 d) #

(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertSym1 d) #

(SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectSym1 d) #

SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersperseSym1 d) #

SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (NubBySym1 d) #

SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanl1Sym1 d) #

SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanr1Sym1 d) #

SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SortBySym1 d) #

SingI d => SingI (TakeSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeSym1 d :: TyFun [a] [a] -> Type) #

SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeWhileSym1 d) #

(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionSym1 d) #

(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((\\@#@$$) d) #

SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:@#@$$) d) #

SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((++@#@$$) d) #

SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Foldl1'Sym1 d) #

SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (GenericLengthSym0 :: TyFun [a] i -> Type) #

(SShow a, SingI d) => SingI (ShowListSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym1 d) #

(SingI d1, SingI d2) => SingI (ShowParenSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym2 d1 d2) #

(SShow a, SingI d) => SingI (ShowsSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym1 d) #

SingI (LeftSym0 :: TyFun a (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (LeftSym0 :: TyFun a (Either a b) -> Type) #

(SOrd a, SingI d) => SingI (CompareSym1 d :: TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (CompareSym1 d) #

SingI ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) #

SingI d => SingI (Bool_Sym1 d :: TyFun a (Bool ~> a) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (Bool_Sym1 d) #

SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) #

SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteBySym1 d) #

SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertBySym1 d) #

(SShow a, SingI d) => SingI (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) #

(SEnum a, SingI d) => SingI (EnumFromThenToSym1 d :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SingI (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sing :: Sing (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) #

SingI (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) #

SingI (ConstSym0 :: TyFun a (b ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (ConstSym0 :: TyFun a (b ~> a) -> Type) #

SingI (SeqSym0 :: TyFun a (b ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (SeqSym0 :: TyFun a (b ~> b) -> Type) #

SingI (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sing :: Sing (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) #

(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) #

(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) #

(SEq a, SingI d) => SingI ((/=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((/=@#@$$) d) #

(SEq a, SingI d) => SingI ((==@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((==@#@$$) d) #

(SOrd a, SingI d) => SingI ((<=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<=@#@$$) d) #

(SOrd a, SingI d) => SingI ((<@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<@#@$$) d) #

(SOrd a, SingI d) => SingI ((>=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>=@#@$$) d) #

(SOrd a, SingI d) => SingI ((>@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>@#@$$) d) #

SingI d => SingI (ReplicateSym1 d :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReplicateSym1 d :: TyFun a [a] -> Type) #

(SEnum a, SingI d) => SingI (EnumFromToSym1 d :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromToSym1 d) #

(SMonoid a, SingI d) => SingI (MappendSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MappendSym1 d) #

(SOrd a, SingI d) => SingI (MaxSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MaxSym1 d) #

(SOrd a, SingI d) => SingI (MinSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MinSym1 d) #

(SSemigroup a, SingI d) => SingI ((<>@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing ((<>@#@$$) d) #

SingI d => SingI (AsTypeOfSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (AsTypeOfSym1 d) #

(SNum a, SingI d) => SingI ((*@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((*@#@$$) d) #

(SNum a, SingI d) => SingI ((+@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((+@#@$$) d) #

(SNum a, SingI d) => SingI ((-@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((-@#@$$) d) #

(SNum a, SingI d) => SingI (SubtractSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SubtractSym1 d) #

SApplicative f => SingI (PureSym0 :: TyFun a (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (PureSym0 :: TyFun a (f a) -> Type) #

SMonad m => SingI (ReturnSym0 :: TyFun a (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (ReturnSym0 :: TyFun a (m a) -> Type) #

SingI (RightSym0 :: TyFun b (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (RightSym0 :: TyFun b (Either a b) -> Type) #

SingI (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) #

(SApplicative f, SingI d) => SingI (UnlessSym1 d :: TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (UnlessSym1 d :: TyFun (f ()) (f ()) -> Type) #

(SApplicative f, SingI d) => SingI (WhenSym1 d :: TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (WhenSym1 d :: TyFun (f ()) (f ()) -> Type) #

SAlternative f => SingI ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) #

SAlternative f => SingI (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) Source # 
Instance details

Defined in Control.Applicative.Singletons

Methods

sing :: Sing (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) #

SFunctor f => SingI (VoidSym0 :: TyFun (f a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (VoidSym0 :: TyFun (f a) (f ()) -> Type) #

SMonadPlus m => SingI (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) #

SMonad m => SingI (JoinSym0 :: TyFun (m (m a)) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (JoinSym0 :: TyFun (m (m a)) (m a) -> Type) #

SingI (ShowTypeSym0 :: TyFun t (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatSym0 :: TyFun (t [a]) [a] -> Type) #

SFoldable t => SingI (LengthSym0 :: TyFun (t a) Natural -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (LengthSym0 :: TyFun (t a) Natural -> Type) #

SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NullSym0 :: TyFun (t a) Bool -> Type) #

SFoldable t => SingI (ToListSym0 :: TyFun (t a) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ToListSym0 :: TyFun (t a) [a] -> Type) #

(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MaximumSym0 :: TyFun (t a) a -> Type) #

(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MinimumSym0 :: TyFun (t a) a -> Type) #

(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ProductSym0 :: TyFun (t a) a -> Type) #

(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (SumSym0 :: TyFun (t a) a -> Type) #

(SFoldable t, SMonoid m) => SingI (FoldSym0 :: TyFun (t m) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldSym0 :: TyFun (t m) m -> Type) #

SingI x => SingI ((<=?@#@$$) x :: TyFun Natural Bool -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing ((<=?@#@$$) x) #

SingI c => SingI (IfSym1 c :: TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym1 c :: TyFun k (k ~> k) -> Type) #

SingI n => SingI ('Left n :: Either a b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ('Left n :: Either a b) #

SingI n => SingI ('Right n :: Either a b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ('Right n :: Either a b) #

SingI a => SingI ('WrapSing s :: WrappedSing a) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing ('WrapSing s :: WrappedSing a) #

(SOrd b, SingI d) => SingI (GroupAllWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

(SEq b, SingI d) => SingI (GroupWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWith1Sym1 d) #

(SOrd o, SingI d) => SingI (SortWithSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortWithSym1 d) #

SingI d => SingI (MapSym1 d :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (MapSym1 d) #

SingI d => SingI (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) #

SingI (GetConstSym0 :: TyFun (Const a b) a -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sing :: Sing (GetConstSym0 :: TyFun (Const a b) a -> Type) #

SingI (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) #

SFoldable t => SingI (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) #

SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) #

SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) #

SingI (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) #

SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) #

SingI (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) #

SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) #

SingI d => SingI (Maybe_Sym1 d :: TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym1 d :: TyFun (a ~> b) (Maybe a ~> b) -> Type) #

SFunctor f => SingI (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SApplicative f => SingI (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SFunctor f => SingI ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SMonad m => SingI ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) #

STraversable t => SingI (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) #

SingI d => SingI ((&@#@$$) d :: TyFun (a ~> b) b -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing ((&@#@$$) d :: TyFun (a ~> b) b -> Type) #

SingI (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) #

(SFoldable t, SMonoid m) => SingI (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) #

(STraversable t, SMonoid m) => SingI (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) #

SMonad m => SingI ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) #

SMonad m => SingI (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) #

SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) #

SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) #

SingI (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) #

SingI ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) #

(SingI d1, SingI d2) => SingI (Bool_Sym2 d1 d2 :: TyFun Bool a -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (Bool_Sym2 d1 d2) #

(SEq a, SingI d) => SingI (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) #

SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) #

SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) #

(SOrd b, SingI d) => SingI (GroupAllWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupAllWithSym1 d) #

(SEq b, SingI d) => SingI (GroupWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWithSym1 d) #

(SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteBySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteFirstsBySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertBySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectBySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionBySym2 d1 d2) #

SingI d => SingI (MapMaybeSym1 d :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (MapMaybeSym1 d) #

SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (MapSym1 d) #

(SApplicative m, SingI d) => SingI (FilterMSym1 d :: TyFun [a] (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (FilterMSym1 d) #

SingI d => SingI (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) #

(SingI d1, SingI d2) => SingI (ShowListWithSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym2 d1 d2) #

(SShow a, SingI d1, SingI d2) => SingI (ShowsPrecSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym2 d1 d2) #

SingI d => SingI (UnfoldSym1 d :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldSym1 d) #

SingI d => SingI (UnfoldrSym1 d :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldrSym1 d) #

SingI (ConstSym0 :: TyFun a (Const a b) -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sing :: Sing (ConstSym0 :: TyFun a (Const a b) -> Type) #

SingI (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) #

SFunctor f => SingI ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) #

(SEnum a, SingI d1, SingI d2) => SingI (EnumFromThenToSym2 d1 d2 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromThenToSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (UntilSym2 d1 d2 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym2 d1 d2) #

SingI d => SingI (($!@#@$$) d :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($!@#@$$) d) #

SingI d => SingI (($@#@$$) d :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($@#@$$) d) #

SingI d => SingI (ArgSym1 d :: TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sing :: Sing (ArgSym1 d :: TyFun b (Arg a b) -> Type) #

SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanlSym1 d) #

SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanrSym1 d) #

SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym1 d) #

SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym1 d) #

(SOrd a, SingI d) => SingI (ComparingSym1 d :: TyFun b (b ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (ComparingSym1 d) #

SingI d => SingI (Tuple2Sym1 d :: TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple2Sym1 d :: TyFun b (a, b) -> Type) #

SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnfoldrSym1 d) #

SingI d => SingI (ConstSym1 d :: TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (ConstSym1 d :: TyFun b a -> Type) #

SingI d => SingI (SeqSym1 d :: TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (SeqSym1 d :: TyFun b b -> Type) #

SApplicative f => SingI ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) #

SFunctor f => SingI ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) #

SFunctor f => SingI (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) #

SApplicative f => SingI ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) #

SApplicative f => SingI ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) #

SApplicative f => SingI ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) #

(SAlternative f, SingI d) => SingI ((<|>@#@$$) d :: TyFun (f a) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<|>@#@$$) d) #

SMonad m => SingI (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) #

SMonadZip m => SingI (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) #

SMonad m => SingI ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) #

SMonadZip m => SingI (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) #

SMonad m => SingI ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) #

(SApplicative m, SingI d) => SingI (ReplicateM_Sym1 d :: TyFun (m a) (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ReplicateM_Sym1 d :: TyFun (m a) (m ()) -> Type) #

(SApplicative m, SingI d) => SingI (ReplicateMSym1 d :: TyFun (m a) (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ReplicateMSym1 d :: TyFun (m a) (m [a]) -> Type) #

(SMonadPlus m, SingI d) => SingI (MfilterSym1 d :: TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (MfilterSym1 d :: TyFun (m a) (m a) -> Type) #

(SMonadPlus m, SingI d) => SingI (MplusSym1 d :: TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (MplusSym1 d) #

SingI d => SingI (AsProxyTypeOfSym1 d :: TyFun (proxy a) a -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sing :: Sing (AsProxyTypeOfSym1 d :: TyFun (proxy a) a -> Type) #

(SFoldable t, SingI d) => SingI (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) #

(SFoldable t, SingI d) => SingI (AllSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AllSym1 d :: TyFun (t a) Bool -> Type) #

(SFoldable t, SingI d) => SingI (AnySym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AnySym1 d :: TyFun (t a) Bool -> Type) #

(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ElemSym1 d :: TyFun (t a) Bool -> Type) #

(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NotElemSym1 d :: TyFun (t a) Bool -> Type) #

(SFoldable t, SingI d) => SingI (Foldl1Sym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl1Sym1 d :: TyFun (t a) a -> Type) #

(SFoldable t, SingI d) => SingI (Foldr1Sym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr1Sym1 d :: TyFun (t a) a -> Type) #

(SFoldable t, SingI d) => SingI (MaximumBySym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MaximumBySym1 d :: TyFun (t a) a -> Type) #

(SFoldable t, SingI d) => SingI (MinimumBySym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MinimumBySym1 d :: TyFun (t a) a -> Type) #

(SFoldable t, SApplicative f) => SingI (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) #

(SFoldable t, SAlternative f) => SingI (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) #

(STraversable t, SApplicative f) => SingI (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) #

(SFoldable t, SMonad m) => SingI (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) #

(SFoldable t, SMonadPlus m) => SingI (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) #

(STraversable t, SMonad m) => SingI (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) #

(SingI c, SingI t) => SingI (IfSym2 c t :: TyFun k k -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym2 c t) #

(forall (a :: k1). SingI a => SingI (f a), (ApplyTyCon :: (k1 -> kr) -> TyFun k1 kr -> Type) ~ (ApplyTyConAux1 :: (k1 -> kr) -> TyFun k1 kr -> Type)) => SingI (TyCon1 f :: TyFun k1 kr -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon1 f) #

(SingI n1, SingI n2) => SingI ('Arg n1 n2 :: Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sing :: Sing ('Arg n1 n2) #

SingI d => SingI (ZipWithSym1 d :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipWithSym1 d) #

SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) #

STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) #

STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) #

SApplicative f => SingI (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) #

SMonadZip m => SingI (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) #

(SFoldable t, SMonad m) => SingI (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) #

SApplicative m => SingI (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) #

SApplicative m => SingI (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) #

SingI d => SingI (OnSym1 d :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym1 d :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) #

SingI d => SingI ((.@#@$$) d :: TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((.@#@$$) d :: TyFun (a ~> b) (a ~> c) -> Type) #

(SFunctor f, SingI d) => SingI ((<&>@#@$$) d :: TyFun (a ~> b) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<&>@#@$$) d :: TyFun (a ~> b) (f b) -> Type) #

(SFoldable t, SApplicative f) => SingI (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) #

(STraversable t, SApplicative f) => SingI (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) #

SApplicative m => SingI (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) #

SMonad m => SingI ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) #

(SFoldable t, SMonad m) => SingI (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) #

(STraversable t, SMonad m) => SingI (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) #

(SMonad m, SingI d) => SingI ((>>=@#@$$) d :: TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>=@#@$$) d :: TyFun (a ~> m b) (m b) -> Type) #

SMonad m => SingI (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) #

(SFoldable t, SMonad m) => SingI (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) #

SingI d => SingI (Either_Sym1 d :: TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym1 d :: TyFun (b ~> c) (Either a b ~> c) -> Type) #

SMonad m => SingI ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) #

(SingI d1, SingI d2) => SingI (Maybe_Sym2 d1 d2 :: TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym2 d1 d2) #

SingI d => SingI (UncurrySym1 d :: TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (UncurrySym1 d) #

SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) #

(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanlSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanrSym2 d1 d2) #

SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym1 d) #

(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym2 d1 d2) #

SingI d => SingI (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) #

SingI (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) #

SingI d => SingI (CurrySym1 d :: TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym1 d) #

(SOrd a, SingI d1, SingI d2) => SingI (ComparingSym2 d1 d2 :: TyFun b Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (ComparingSym2 d1 d2) #

SingI d => SingI (FlipSym1 d :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym1 d) #

SingI d => SingI (Tuple3Sym1 d :: TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym1 d :: TyFun b (c ~> (a, b, c)) -> Type) #

(SFoldable t, SingI d) => SingI (Foldl'Sym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl'Sym1 d :: TyFun b (t a ~> b) -> Type) #

(SFoldable t, SingI d) => SingI (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) #

(SFoldable t, SingI d) => SingI (Foldr'Sym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr'Sym1 d :: TyFun b (t a ~> b) -> Type) #

(SFoldable t, SingI d) => SingI (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) #

(SFunctor f, SingI d) => SingI (($>@#@$$) d :: TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (($>@#@$$) d :: TyFun b (f b) -> Type) #

(SApplicative f, SingI d) => SingI ((<**>@#@$$) d :: TyFun (f (a ~> b)) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<**>@#@$$) d :: TyFun (f (a ~> b)) (f b) -> Type) #

SingI (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sing :: Sing (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) #

SingI (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sing :: Sing (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) #

(SApplicative f, SingI d) => SingI ((<*>@#@$$) d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*>@#@$$) d) #

(SFunctor f, SingI d) => SingI (FmapSym1 d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (FmapSym1 d :: TyFun (f a) (f b) -> Type) #

(SApplicative f, SingI d) => SingI (LiftASym1 d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftASym1 d :: TyFun (f a) (f b) -> Type) #

(SFunctor f, SingI d) => SingI ((<$>@#@$$) d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<$>@#@$$) d :: TyFun (f a) (f b) -> Type) #

(SFunctor f, SingI d) => SingI ((<$@#@$$) d :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<$@#@$$) d :: TyFun (f b) (f a) -> Type) #

(SApplicative f, SingI d) => SingI ((<*@#@$$) d :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*@#@$$) d :: TyFun (f b) (f a) -> Type) #

(SApplicative f, SingI d) => SingI ((*>@#@$$) d :: TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((*>@#@$$) d :: TyFun (f b) (f b) -> Type) #

SingI (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sing :: Sing (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) #

(SMonad m, SingI d) => SingI ((<$!>@#@$$) d :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((<$!>@#@$$) d :: TyFun (m a) (m b) -> Type) #

(SMonad m, SingI d) => SingI ((=<<@#@$$) d :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((=<<@#@$$) d) #

(SMonad m, SingI d) => SingI (ApSym1 d :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (ApSym1 d) #

(SMonad m, SingI d) => SingI (LiftMSym1 d :: TyFun (m a1) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftMSym1 d :: TyFun (m a1) (m r) -> Type) #

(SMonadZip m, SingI d) => SingI (MzipSym1 d :: TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipSym1 d :: TyFun (m b) (m (a, b)) -> Type) #

(SMonad m, SingI d) => SingI ((>>@#@$$) d :: TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>@#@$$) d :: TyFun (m b) (m b) -> Type) #

(SFoldable t, SApplicative f) => SingI (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) #

(STraversable t, SApplicative f) => SingI (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) #

(SFoldable t, SMonad m) => SingI (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) #

(STraversable t, SMonad m) => SingI (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) #

(SFoldable t, SingI d) => SingI (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) #

(SFoldable t, SMonoid m, SingI d) => SingI (FoldMapSym1 d :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldMapSym1 d :: TyFun (t a) m -> Type) #

(STraversable t, SMonoid m, SingI d) => SingI (FoldMapDefaultSym1 d :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (FoldMapDefaultSym1 d :: TyFun (t a) m -> Type) #

(STraversable t, SingI d) => SingI (FmapDefaultSym1 d :: TyFun (t a) (t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (FmapDefaultSym1 d :: TyFun (t a) (t b) -> Type) #

(SingI n1, SingI n2) => SingI ('(n1, n2) :: (a, b)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing '(n1, n2) #

(forall (a :: k1) (b :: k2). (SingI a, SingI b) => SingI (f a b), (ApplyTyCon :: (k2 -> kr) -> TyFun k2 kr -> Type) ~ (ApplyTyConAux1 :: (k2 -> kr) -> TyFun k2 kr -> Type)) => SingI (TyCon2 f :: TyFun k1 (k2 ~> kr) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon2 f) #

SingI (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sing :: Sing (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) #

(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipWithSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (Either_Sym2 d1 d2 :: TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym2 d1 d2) #

SApplicative f => SingI (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) #

(SFoldable t, SApplicative f, SingI d) => SingI (For_Sym1 d :: TyFun (a ~> f b) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (For_Sym1 d :: TyFun (a ~> f b) (f ()) -> Type) #

(STraversable t, SApplicative f, SingI d) => SingI (ForSym1 d :: TyFun (a ~> f b) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (ForSym1 d :: TyFun (a ~> f b) (f (t b)) -> Type) #

(SMonad m, SingI d) => SingI ((<=<@#@$$) d :: TyFun (a ~> m b) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((<=<@#@$$) d :: TyFun (a ~> m b) (a ~> m c) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (ForM_Sym1 d :: TyFun (a ~> m b) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ForM_Sym1 d :: TyFun (a ~> m b) (m ()) -> Type) #

(STraversable t, SMonad m, SingI d) => SingI (ForMSym1 d :: TyFun (a ~> m b) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (ForMSym1 d :: TyFun (a ~> m b) (m (t b)) -> Type) #

SMonad m => SingI (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) #

(SMonad m, SingI d) => SingI ((>=>@#@$$) d :: TyFun (b ~> m c) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((>=>@#@$$) d :: TyFun (b ~> m c) (a ~> m c) -> Type) #

SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) #

SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym1 d2) #

(SApplicative m, SingI d) => SingI (ZipWithM_Sym1 d :: TyFun [a] ([b] ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithM_Sym1 d) #

(SApplicative m, SingI d) => SingI (ZipWithMSym1 d :: TyFun [a] ([b] ~> m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithMSym1 d) #

(SApplicative m, SingI d) => SingI (MapAndUnzipMSym1 d :: TyFun [a] (m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (MapAndUnzipMSym1 d) #

(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) #

(SingI d1, SingI d2) => SingI (OnSym2 d1 d2 :: TyFun a (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym2 d1 d2) #

SingI (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) #

(STraversable t, SingI d) => SingI (MapAccumLSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumLSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) #

(STraversable t, SingI d) => SingI (MapAccumRSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumRSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) #

(SingI d1, SingI d2) => SingI (d1 .@#@$$$ d2 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (d1 .@#@$$$ d2) #

(SingI d1, SingI d2) => SingI (FlipSym2 d1 d2 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym2 d1 d2) #

SingI d1 => SingI (Tuple4Sym1 d1 :: TyFun b (c ~> (d2 ~> (a, b, c, d2))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym1 d1 :: TyFun b (c ~> (d2 ~> (a, b, c, d2))) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (FoldlMSym1 d :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlMSym1 d :: TyFun b (t a ~> m b) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (FoldrMSym1 d :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrMSym1 d :: TyFun b (t a ~> m b) -> Type) #

(SingI d1, SingI d2) => SingI (CurrySym2 d1 d2 :: TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (Tuple3Sym2 d1 d2 :: TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym2 d1 d2 :: TyFun c (a, b, c) -> Type) #

(SApplicative f, SingI d) => SingI (LiftA2Sym1 d :: TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym1 d :: TyFun (f a) (f b ~> f c) -> Type) #

SingI (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sing :: Sing (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) #

SingI d => SingI (PairSym1 d :: TyFun (g a) (Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sing :: Sing (PairSym1 d :: TyFun (g a) (Product f g a) -> Type) #

(SMonadZip m, SingI d) => SingI (MzipWithSym1 d :: TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym1 d :: TyFun (m a) (m b ~> m c) -> Type) #

(SMonad m, SingI d) => SingI (LiftM2Sym1 d :: TyFun (m a1) (m a2 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM2Sym1 d :: TyFun (m a1) (m a2 ~> m r) -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl'Sym2 d1 d2 :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (Foldr'Sym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr'Sym2 d1 d2 :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) #

(SFoldable t, SApplicative f, SingI d) => SingI (Traverse_Sym1 d :: TyFun (t a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Traverse_Sym1 d :: TyFun (t a) (f ()) -> Type) #

(STraversable t, SApplicative f, SingI d) => SingI (TraverseSym1 d :: TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (TraverseSym1 d :: TyFun (t a) (f (t b)) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (MapM_Sym1 d :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MapM_Sym1 d :: TyFun (t a) (m ()) -> Type) #

(STraversable t, SMonad m, SingI d) => SingI (MapMSym1 d :: TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapMSym1 d :: TyFun (t a) (m (t b)) -> Type) #

(SingI fst, SingI b) => SingI (a ':&: b :: Sigma s t) # 
Instance details

Defined in Data.Singletons.Sigma

Methods

sing :: Sing (a ':&: b :: Sigma s t) #

(forall (a :: k1) (b :: k2) (c :: k3). (SingI a, SingI b, SingI c) => SingI (f a b c), (ApplyTyCon :: (k3 -> kr) -> TyFun k3 kr -> Type) ~ (ApplyTyConAux1 :: (k3 -> kr) -> TyFun k3 kr -> Type)) => SingI (TyCon3 f :: TyFun k1 (k2 ~> (k3 ~> kr)) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon3 f) #

SMonad m => SingI (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) #

SingI (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) #

(SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym2 d2 d3) #

(SApplicative m, SingI d1, SingI d2) => SingI (ZipWithM_Sym2 d1 d2 :: TyFun [b] (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithM_Sym2 d1 d2) #

(SApplicative m, SingI d1, SingI d2) => SingI (ZipWithMSym2 d1 d2 :: TyFun [b] (m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithMSym2 d1 d2) #

SingI (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (OnSym3 d1 d2 d3 :: TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym3 d1 d2 d3) #

(SMonad m, SingI d1, SingI d2) => SingI (d1 <=<@#@$$$ d2 :: TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (d1 <=<@#@$$$ d2) #

(SMonad m, SingI d1, SingI d2) => SingI (d1 >=>@#@$$$ d2 :: TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (d1 >=>@#@$$$ d2) #

SingI d1 => SingI (Tuple5Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (a, b, c, d2, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (a, b, c, d2, e)))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple4Sym2 d1 d2 :: TyFun c (d3 ~> (a, b, c, d3)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym2 d1 d2 :: TyFun c (d3 ~> (a, b, c, d3)) -> Type) #

(SApplicative f, SingI d2) => SingI (LiftA3Sym1 d2 :: TyFun (f a) (f b ~> (f c ~> f d1)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA3Sym1 d2 :: TyFun (f a) (f b ~> (f c ~> f d1)) -> Type) #

(SApplicative f, SingI d1, SingI d2) => SingI (LiftA2Sym2 d1 d2 :: TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym2 d1 d2) #

(SMonad m, SingI d) => SingI (LiftM3Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM3Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) #

(SMonad m, SingI d1, SingI d2) => SingI (LiftM2Sym2 d1 d2 :: TyFun (m a2) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM2Sym2 d1 d2) #

(SMonadZip m, SingI d1, SingI d2) => SingI (MzipWithSym2 d1 d2 :: TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym2 d1 d2) #

(SFoldable t, SMonad m, SingI d1, SingI d2) => SingI (FoldlMSym2 d1 d2 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlMSym2 d1 d2 :: TyFun (t a) (m b) -> Type) #

(SFoldable t, SMonad m, SingI d1, SingI d2) => SingI (FoldrMSym2 d1 d2 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrMSym2 d1 d2 :: TyFun (t a) (m b) -> Type) #

(STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumLSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) #

(STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumRSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4). (SingI a, SingI b, SingI c, SingI d) => SingI (f a b c d), (ApplyTyCon :: (k4 -> kr) -> TyFun k4 kr -> Type) ~ (ApplyTyConAux1 :: (k4 -> kr) -> TyFun k4 kr -> Type)) => SingI (TyCon4 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> kr))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon4 f) #

SMonad m => SingI (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) #

SingI (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) #

(SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym3 d2 d3 d4) #

SingI (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) #

SingI d1 => SingI (Tuple6Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f))))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple5Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (a, b, c, d3, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (a, b, c, d3, e))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple4Sym3 d1 d2 d3 :: TyFun d4 (a, b, c, d4) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym3 d1 d2 d3 :: TyFun d4 (a, b, c, d4) -> Type) #

(SApplicative f, SingI d2, SingI d3) => SingI (LiftA3Sym2 d2 d3 :: TyFun (f b) (f c ~> f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA3Sym2 d2 d3) #

(SMonad m, SingI d) => SingI (LiftM4Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) #

(SMonad m, SingI d1, SingI d2) => SingI (LiftM3Sym2 d1 d2 :: TyFun (m a2) (m a3 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM3Sym2 d1 d2) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5). (SingI a, SingI b, SingI c, SingI d, SingI e) => SingI (f a b c d e), (ApplyTyCon :: (k5 -> kr) -> TyFun k5 kr -> Type) ~ (ApplyTyConAux1 :: (k5 -> kr) -> TyFun k5 kr -> Type)) => SingI (TyCon5 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> kr)))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon5 f) #

SingI d1 => SingI (Tuple7Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple6Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (a, b, c, d3, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (a, b, c, d3, e, f)))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple5Sym3 d1 d2 d3 :: TyFun d4 (e ~> (a, b, c, d4, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym3 d1 d2 d3 :: TyFun d4 (e ~> (a, b, c, d4, e)) -> Type) #

(SApplicative f, SingI d2, SingI d3, SingI d4) => SingI (LiftA3Sym3 d2 d3 d4 :: TyFun (f c) (f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA3Sym3 d2 d3 d4) #

(SMonad m, SingI d) => SingI (LiftM5Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) #

(SMonad m, SingI d1, SingI d2) => SingI (LiftM4Sym2 d1 d2 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym2 d1 d2) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI (LiftM3Sym3 d1 d2 d3 :: TyFun (m a3) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM3Sym3 d1 d2 d3) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f') => SingI (f a b c d e f'), (ApplyTyCon :: (k6 -> kr) -> TyFun k6 kr -> Type) ~ (ApplyTyConAux1 :: (k6 -> kr) -> TyFun k6 kr -> Type)) => SingI (TyCon6 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> kr))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon6 f) #

(SingI d1, SingI d2) => SingI (Tuple7Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g))))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple6Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (a, b, c, d4, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (a, b, c, d4, e, f))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple5Sym4 d1 d2 d3 d5 :: TyFun e (a, b, c, d4, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym4 d1 d2 d3 d5 :: TyFun e (a, b, c, d4, e) -> Type) #

(SMonad m, SingI d1, SingI d2) => SingI (LiftM5Sym2 d1 d2 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym2 d1 d2) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI (LiftM4Sym3 d1 d2 d3 :: TyFun (m a3) (m a4 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym3 d1 d2 d3) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6) (g :: k7). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f', SingI g) => SingI (f a b c d e f' g), (ApplyTyCon :: (k7 -> kr) -> TyFun k7 kr -> Type) ~ (ApplyTyConAux1 :: (k7 -> kr) -> TyFun k7 kr -> Type)) => SingI (TyCon7 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> kr)))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon7 f) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple7Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (g ~> (a, b, c, d4, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (g ~> (a, b, c, d4, e, f, g)))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple6Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI (LiftM5Sym3 d1 d2 d3 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym3 d1 d2 d3) #

(SMonad m, SingI d1, SingI d2, SingI d3, SingI d4) => SingI (LiftM4Sym4 d1 d2 d3 d4 :: TyFun (m a4) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym4 d1 d2 d3 d4) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6) (g :: k7) (h :: k8). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f', SingI g, SingI h) => SingI (f a b c d e f' g h), (ApplyTyCon :: (k8 -> kr) -> TyFun k8 kr -> Type) ~ (ApplyTyConAux1 :: (k8 -> kr) -> TyFun k8 kr -> Type)) => SingI (TyCon8 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k8 ~> kr))))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon8 f) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple7Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI (Tuple6Sym5 d1 d2 d3 d5 d6 :: TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym5 d1 d2 d3 d5 d6 :: TyFun f (a, b, c, d4, e, f) -> Type) #

(SMonad m, SingI d1, SingI d2, SingI d3, SingI d4) => SingI (LiftM5Sym4 d1 d2 d3 d4 :: TyFun (m a4) (m a5 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI (Tuple7Sym5 d1 d2 d3 d5 d6 :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym5 d1 d2 d3 d5 d6 :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

(SMonad m, SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (LiftM5Sym5 d1 d2 d3 d4 d5 :: TyFun (m a5) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym5 d1 d2 d3 d4 d5) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6, SingI d7) => SingI (Tuple7Sym6 d1 d2 d3 d5 d6 d7 :: TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym6 d1 d2 d3 d5 d6 d7 :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

SingI n => SingI ('Const n :: Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sing :: Sing ('Const n :: Const a b) #

(SingI n1, SingI n2, SingI n3) => SingI ('(n1, n2, n3) :: (a, b, c)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing '(n1, n2, n3) #

SingI n => SingI ('InL n :: Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sing :: Sing ('InL n :: Sum f g a) #

SingI n => SingI ('InR n :: Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sing :: Sing ('InR n :: Sum f g a) #

(SingI n1, SingI n2) => SingI ('Pair n1 n2 :: Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sing :: Sing ('Pair n1 n2) #

(SingI n1, SingI n2, SingI n3, SingI n4) => SingI ('(n1, n2, n3, n4) :: (a, b, c, d)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing '(n1, n2, n3, n4) #

SingI n => SingI ('Compose n :: Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sing :: Sing ('Compose n) #

(SingI n1, SingI n2, SingI n3, SingI n4, SingI n5) => SingI ('(n1, n2, n3, n4, n5) :: (a, b, c, d, e)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing '(n1, n2, n3, n4, n5) #

(SingI n1, SingI n2, SingI n3, SingI n4, SingI n5, SingI n6) => SingI ('(n1, n2, n3, n4, n5, n6) :: (a, b, c, d, e, f)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing '(n1, n2, n3, n4, n5, n6) #

(SingI n1, SingI n2, SingI n3, SingI n4, SingI n5, SingI n6, SingI n7) => SingI ('(n1, n2, n3, n4, n5, n6, n7) :: (a, b, c, d, e, f, g)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing '(n1, n2, n3, n4, n5, n6, n7) #

class (forall (x :: k1). SingI x => SingI (f x)) => SingI1 (f :: k1 -> k2) where #

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (f x) #

Instances

Instances details
SingI1 'All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing ('All x) #

SingI1 'Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing ('Any x) #

SingI1 ('Text :: Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: Symbol). Sing x -> Sing ('Text x) #

SingI e1 => SingI1 ('(:$$:) e1 :: ErrorMessage' Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing (e1 ':$$: x) #

SingI e1 => SingI1 ('(:<>:) e1 :: ErrorMessage' Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing (e1 ':<>: x) #

SingI1 ('ShowType :: t -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: t). Sing x -> Sing ('ShowType x :: ErrorMessage' Symbol) #

SingI1 ('First :: k1 -> First k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('First x) #

SingI1 ('Last :: k1 -> Last k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Last x) #

SingI1 ('Max :: k1 -> Max k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Max x) #

SingI1 ('Min :: k1 -> Min k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Min x) #

SingI1 ('WrapMonoid :: k1 -> WrappedMonoid k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('WrapMonoid x) #

SingI1 ('Identity :: k1 -> Identity k1) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Identity x) #

SingI1 ('Down :: k1 -> Down k1) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Down x) #

SingI1 ('Dual :: k1 -> Dual k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Dual x) #

SingI1 ('Product :: k1 -> Product k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Product x) #

SingI1 ('Sum :: k1 -> Sum k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Sum x) #

SingI1 ('Just :: k1 -> Maybe k1) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Just x) #

SingI1 DivSym1 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (DivSym1 x) #

SingI1 ModSym1 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ModSym1 x) #

SingI1 (^@#@$$) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing ((^@#@$$) x) #

SingI1 ShowParenSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (ShowParenSym1 x) #

SingI1 ShowCharSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Char). Sing x -> Sing (ShowCharSym1 x) #

SingI1 ConsSymbolSym1 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

liftSing :: forall (x :: Char). Sing x -> Sing (ConsSymbolSym1 x) #

SingI1 ShowStringSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol). Sing x -> Sing (ShowStringSym1 x) #

SingI1 ((:$$:@#@$$) :: ErrorMessage' Symbol -> TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing ((:$$:@#@$$) x) #

SingI1 ((:<>:@#@$$) :: ErrorMessage' Symbol -> TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing ((:<>:@#@$$) x) #

SingI1 (SplitAtSym1 :: Natural -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (SplitAtSym1 x :: TyFun (NonEmpty a) ([a], [a]) -> Type) #

SingI1 (DropSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (DropSym1 x :: TyFun (NonEmpty a) [a] -> Type) #

SingI1 (TakeSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (TakeSym1 x :: TyFun (NonEmpty a) [a] -> Type) #

SingI1 (SplitAtSym1 :: Natural -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (SplitAtSym1 x :: TyFun [a] ([a], [a]) -> Type) #

SingI1 (DropSym1 :: Natural -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (DropSym1 x :: TyFun [a] [a] -> Type) #

SingI1 (TakeSym1 :: Natural -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (TakeSym1 x :: TyFun [a] [a] -> Type) #

SShow a => SingI1 (ShowsPrecSym1 :: Natural -> TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ShowsPrecSym1 x :: TyFun a (Symbol ~> Symbol) -> Type) #

SingI1 (ReplicateSym1 :: Natural -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ReplicateSym1 x :: TyFun a [a] -> Type) #

SingI1 ((<=?@#@$$) :: Natural -> TyFun Natural Bool -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing ((<=?@#@$$) x) #

SApplicative f => SingI1 (UnlessSym1 :: Bool -> TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (UnlessSym1 x :: TyFun (f ()) (f ()) -> Type) #

SApplicative f => SingI1 (WhenSym1 :: Bool -> TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (WhenSym1 x :: TyFun (f ()) (f ()) -> Type) #

SingI1 (IfSym1 :: Bool -> TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (IfSym1 x :: TyFun k (k ~> k) -> Type) #

SingI1 ((<|@#@$$) :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<|@#@$$) x) #

SingI1 (ConsSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ConsSym1 x) #

SingI1 (IntersperseSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (IntersperseSym1 x) #

SingI1 (FromMaybeSym1 :: a -> TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (FromMaybeSym1 x) #

SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (InsertSym1 x) #

SingI1 ((:|@#@$$) :: a -> TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((:|@#@$$) x) #

SEq a => SingI1 (ElemIndexSym1 :: a -> TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ElemIndexSym1 x) #

SEq a => SingI1 (ElemIndicesSym1 :: a -> TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ElemIndicesSym1 x) #

SEq a => SingI1 (DeleteSym1 :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (DeleteSym1 x) #

SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (InsertSym1 x) #

SingI1 (IntersperseSym1 :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (IntersperseSym1 x) #

SingI1 ((:@#@$$) :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((:@#@$$) x) #

SShow a => SingI1 (ShowsSym1 :: a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsSym1 x) #

SOrd a => SingI1 (CompareSym1 :: a -> TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (CompareSym1 x) #

SingI1 (Bool_Sym1 :: a -> TyFun a (Bool ~> a) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Bool_Sym1 x) #

SEnum a => SingI1 (EnumFromThenToSym1 :: a -> TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromThenToSym1 x) #

SEq a => SingI1 ((/=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((/=@#@$$) x) #

SEq a => SingI1 ((==@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((==@#@$$) x) #

SOrd a => SingI1 ((<=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<=@#@$$) x) #

SOrd a => SingI1 ((<@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<@#@$$) x) #

SOrd a => SingI1 ((>=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((>=@#@$$) x) #

SOrd a => SingI1 ((>@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((>@#@$$) x) #

SEnum a => SingI1 (EnumFromToSym1 :: a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromToSym1 x) #

SMonoid a => SingI1 (MappendSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MappendSym1 x) #

SOrd a => SingI1 (MaxSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MaxSym1 x) #

SOrd a => SingI1 (MinSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MinSym1 x) #

SSemigroup a => SingI1 ((<>@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<>@#@$$) x) #

SingI1 (AsTypeOfSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (AsTypeOfSym1 x) #

SNum a => SingI1 ((*@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((*@#@$$) x) #

SNum a => SingI1 ((+@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((+@#@$$) x) #

SNum a => SingI1 ((-@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((-@#@$$) x) #

SNum a => SingI1 (SubtractSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (SubtractSym1 x) #

SApplicative m => SingI1 (ReplicateM_Sym1 :: Natural -> TyFun (m a) (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ReplicateM_Sym1 x :: TyFun (m a) (m ()) -> Type) #

SApplicative m => SingI1 (ReplicateMSym1 :: Natural -> TyFun (m a) (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ReplicateMSym1 x :: TyFun (m a) (m [a]) -> Type) #

SingI1 ((&@#@$$) :: a -> TyFun (a ~> b) b -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((&@#@$$) x :: TyFun (a ~> b) b -> Type) #

SingI d => SingI1 (Bool_Sym2 d :: a -> TyFun Bool a -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Bool_Sym2 d x) #

SEq a => SingI1 (LookupSym1 :: a -> TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (LookupSym1 x :: TyFun [(a, b)] (Maybe b) -> Type) #

SingI d => SingI1 (DeleteBySym2 d :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (DeleteBySym2 d x) #

SingI d => SingI1 (InsertBySym2 d :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (InsertBySym2 d x) #

(SShow a, SingI d) => SingI1 (ShowsPrecSym2 d :: a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsPrecSym2 d x) #

(SEnum a, SingI d) => SingI1 (EnumFromThenToSym2 d :: a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromThenToSym2 d x) #

SingI1 (ArgSym1 :: a -> TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ArgSym1 x :: TyFun b (Arg a b) -> Type) #

SingI1 (Tuple2Sym1 :: a -> TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple2Sym1 x :: TyFun b (a, b) -> Type) #

SingI1 (ConstSym1 :: a -> TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ConstSym1 x :: TyFun b a -> Type) #

SingI1 (SeqSym1 :: a -> TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (SeqSym1 x :: TyFun b b -> Type) #

SingI1 (AsProxyTypeOfSym1 :: a -> TyFun (proxy a) a -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (AsProxyTypeOfSym1 x :: TyFun (proxy a) a -> Type) #

(SFoldable t, SEq a) => SingI1 (ElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ElemSym1 x :: TyFun (t a) Bool -> Type) #

(SFoldable t, SEq a) => SingI1 (NotElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (NotElemSym1 x :: TyFun (t a) Bool -> Type) #

SingI1 (Maybe_Sym1 :: b -> TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Maybe_Sym1 x :: TyFun (a ~> b) (Maybe a ~> b) -> Type) #

SingI1 ('Right :: k1 -> Either a k1) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Right x :: Either a k1) #

SingI1 ('Left :: k1 -> Either k1 b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Left x :: Either k1 b) #

SingI c => SingI1 (IfSym2 c :: k1 -> TyFun k1 k1 -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (IfSym2 c x) #

SingI1 (Tuple3Sym1 :: a -> TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple3Sym1 x :: TyFun b (c ~> (a, b, c)) -> Type) #

SFunctor f => SingI1 ((<$@#@$$) :: a -> TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<$@#@$$) x :: TyFun (f b) (f a) -> Type) #

SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanlSym2 d x) #

SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanrSym2 d x) #

SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanlSym2 d x) #

SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanrSym2 d x) #

(SOrd a, SingI d) => SingI1 (ComparingSym2 d :: b -> TyFun b Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ComparingSym2 d x) #

SingI n => SingI1 ('Arg n :: k1 -> Arg a k1) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Arg n x) #

SingI n => SingI1 ('(,) n :: k1 -> (a, k1)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing '(n, x) #

SingI1 (Tuple4Sym1 :: a -> TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple4Sym1 x :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) #

SingI d => SingI1 (CurrySym2 d :: a -> TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (CurrySym2 d x) #

SingI d => SingI1 (FlipSym2 d :: b -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FlipSym2 d x) #

SingI d => SingI1 (Tuple3Sym2 d :: b -> TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple3Sym2 d x :: TyFun c (a, b, c) -> Type) #

(SFoldable t, SingI d) => SingI1 (Foldl'Sym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Foldl'Sym2 d x :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d) => SingI1 (FoldlSym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldlSym2 d x :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d) => SingI1 (Foldr'Sym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Foldr'Sym2 d x :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d) => SingI1 (FoldrSym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldrSym2 d x :: TyFun (t a) b -> Type) #

(SingI d1, SingI d2) => SingI1 (OnSym3 d1 d2 :: a -> TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (OnSym3 d1 d2 x) #

SingI1 (Tuple5Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple5Sym1 x :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) #

(STraversable t, SingI d) => SingI1 (MapAccumLSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MapAccumLSym2 d x :: TyFun (t b) (a, t c) -> Type) #

(STraversable t, SingI d) => SingI1 (MapAccumRSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MapAccumRSym2 d x :: TyFun (t b) (a, t c) -> Type) #

SingI d1 => SingI1 (Tuple4Sym2 d1 :: b -> TyFun c (d2 ~> (a, b, c, d2)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple4Sym2 d1 x :: TyFun c (d2 ~> (a, b, c, d2)) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI1 (FoldlMSym2 d :: b -> TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldlMSym2 d x :: TyFun (t a) (m b) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI1 (FoldrMSym2 d :: b -> TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldrMSym2 d x :: TyFun (t a) (m b) -> Type) #

SingI1 (Tuple6Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple6Sym1 x :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) #

SingI d1 => SingI1 (Tuple5Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (a, b, c, d2, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple5Sym2 d1 x :: TyFun c (d2 ~> (e ~> (a, b, c, d2, e))) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple4Sym3 d1 d2 :: c -> TyFun d3 (a, b, c, d3) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple4Sym3 d1 d2 x :: TyFun d3 (a, b, c, d3) -> Type) #

SingI1 (Tuple7Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple7Sym1 x :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) #

SingI d1 => SingI1 (Tuple6Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple6Sym2 d1 x :: TyFun c (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f)))) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple5Sym3 d1 d2 :: c -> TyFun d3 (e ~> (a, b, c, d3, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple5Sym3 d1 d2 x :: TyFun d3 (e ~> (a, b, c, d3, e)) -> Type) #

SingI d1 => SingI1 (Tuple7Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple7Sym2 d1 x :: TyFun c (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g))))) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple6Sym3 d1 d2 :: c -> TyFun d3 (e ~> (f ~> (a, b, c, d3, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple6Sym3 d1 d2 x :: TyFun d3 (e ~> (f ~> (a, b, c, d3, e, f))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple5Sym4 d1 d2 d3 :: d4 -> TyFun e (a, b, c, d4, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple5Sym4 d1 d2 d3 x :: TyFun e (a, b, c, d4, e) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple7Sym3 d1 d2 :: c -> TyFun d3 (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple7Sym3 d1 d2 x :: TyFun d3 (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g)))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple6Sym4 d1 d2 d3 :: d4 -> TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple6Sym4 d1 d2 d3 x :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple7Sym4 d1 d2 d3 :: d4 -> TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple7Sym4 d1 d2 d3 x :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI1 (Tuple6Sym5 d1 d2 d3 d5 :: e -> TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: e). Sing x -> Sing (Tuple6Sym5 d1 d2 d3 d5 x :: TyFun f (a, b, c, d4, e, f) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI1 (Tuple7Sym5 d1 d2 d3 d5 :: e -> TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: e). Sing x -> Sing (Tuple7Sym5 d1 d2 d3 d5 x :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI1 (Tuple7Sym6 d1 d2 d3 d5 d6 :: f -> TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: f). Sing x -> Sing (Tuple7Sym6 d1 d2 d3 d5 d6 x :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

SingI1 ('Const :: k1 -> Const k1 b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Const x :: Const k1 b) #

(SingI n1, SingI n2) => SingI1 ('(,,) n1 n2 :: k1 -> (a, b, k1)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing '(n1, n2, x) #

(SingI n1, SingI n2, SingI n3) => SingI1 ('(,,,) n1 n2 n3 :: k1 -> (a, b, c, k1)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing '(n1, n2, n3, x) #

(SingI n1, SingI n2, SingI n3, SingI n4) => SingI1 ('(,,,,) n1 n2 n3 n4 :: k1 -> (a, b, c, d, k1)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing '(n1, n2, n3, n4, x) #

(SingI n1, SingI n2, SingI n3, SingI n4, SingI n5) => SingI1 ('(,,,,,) n1 n2 n3 n4 n5 :: k1 -> (a, b, c, d, e, k1)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing '(n1, n2, n3, n4, n5, x) #

(SingI n1, SingI n2, SingI n3, SingI n4, SingI n5, SingI n6) => SingI1 ('(,,,,,,) n1 n2 n3 n4 n5 n6 :: k1 -> (a, b, c, d, e, f, k1)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: k1). Sing x -> Sing '(n1, n2, n3, n4, n5, n6, x) #

SingI1 ('First :: Maybe a -> First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

liftSing :: forall (x :: Maybe a). Sing x -> Sing ('First x) #

SingI1 ('Last :: Maybe a -> Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

liftSing :: forall (x :: Maybe a). Sing x -> Sing ('Last x) #

SingI n => SingI1 ('(:|) n :: [a] -> NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (n ':| x) #

SingI n => SingI1 ('(:) n :: [a] -> [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (n ': x) #

SingI1 ((!!@#@$$) :: NonEmpty a -> TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: NonEmpty a). Sing x -> Sing ((!!@#@$$) x) #

SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IsPrefixOfSym1 x) #

SingI1 ((!!@#@$$) :: [a] -> TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing ((!!@#@$$) x) #

SingI1 (IntercalateSym1 :: [a] -> TyFun [[a]] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IntercalateSym1 x) #

SEq a => SingI1 (IsInfixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IsInfixOfSym1 x) #

SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IsPrefixOfSym1 x) #

SEq a => SingI1 (IsSuffixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IsSuffixOfSym1 x) #

SEq a => SingI1 (IntersectSym1 :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IntersectSym1 x) #

SEq a => SingI1 (UnionSym1 :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (UnionSym1 x) #

SEq a => SingI1 ((\\@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing ((\\@#@$$) x) #

SingI1 ((++@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing ((++@#@$$) x) #

SShow a => SingI1 (ShowListSym1 :: [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListSym1 x) #

SingI1 (ZipSym1 :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: NonEmpty a). Sing x -> Sing (ZipSym1 x :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) #

SingI d => SingI1 (DeleteFirstsBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (DeleteFirstsBySym2 d x) #

SingI d => SingI1 (IntersectBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IntersectBySym2 d x) #

SingI d => SingI1 (UnionBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (UnionBySym2 d x) #

SingI1 (ZipSym1 :: [a] -> TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipSym1 x :: TyFun [b] [(a, b)] -> Type) #

SingI d => SingI1 (ShowListWithSym2 d :: [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListWithSym2 d x) #

SAlternative f => SingI1 ((<|>@#@$$) :: f a -> TyFun (f a) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<|>@#@$$) x) #

SMonadPlus m => SingI1 (MplusSym1 :: m a -> TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a). Sing x -> Sing (MplusSym1 x) #

SingI1 (Zip3Sym1 :: [a] -> TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (Zip3Sym1 x :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) #

SApplicative f => SingI1 ((<*>@#@$$) :: f (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f (a ~> b)). Sing x -> Sing ((<*>@#@$$) x) #

SFunctor f => SingI1 ((<&>@#@$$) :: f a -> TyFun (a ~> b) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<&>@#@$$) x :: TyFun (a ~> b) (f b) -> Type) #

SFunctor f => SingI1 (($>@#@$$) :: f a -> TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (($>@#@$$) x :: TyFun b (f b) -> Type) #

SApplicative f => SingI1 ((<**>@#@$$) :: f a -> TyFun (f (a ~> b)) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<**>@#@$$) x :: TyFun (f (a ~> b)) (f b) -> Type) #

SApplicative f => SingI1 ((<*@#@$$) :: f a -> TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<*@#@$$) x :: TyFun (f b) (f a) -> Type) #

SApplicative f => SingI1 ((*>@#@$$) :: f a -> TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((*>@#@$$) x :: TyFun (f b) (f b) -> Type) #

SMonad m => SingI1 (ApSym1 :: m (a ~> b) -> TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m (a ~> b)). Sing x -> Sing (ApSym1 x) #

SMonad m => SingI1 ((>>=@#@$$) :: m a -> TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a). Sing x -> Sing ((>>=@#@$$) x :: TyFun (a ~> m b) (m b) -> Type) #

SMonadZip m => SingI1 (MzipSym1 :: m a -> TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: m a). Sing x -> Sing (MzipSym1 x :: TyFun (m b) (m (a, b)) -> Type) #

SMonad m => SingI1 ((>>@#@$$) :: m a -> TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a). Sing x -> Sing ((>>@#@$$) x :: TyFun (m b) (m b) -> Type) #

SingI d => SingI1 (ZipWithSym2 d :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: NonEmpty a). Sing x -> Sing (ZipWithSym2 d x) #

SingI d => SingI1 (ZipWithSym2 d :: [a] -> TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWithSym2 d x) #

SingI d => SingI1 (Zip3Sym2 d :: [b] -> TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [b]). Sing x -> Sing (Zip3Sym2 d x :: TyFun [c] [(a, b, c)] -> Type) #

SingI1 (PairSym1 :: f a -> TyFun (g a) (Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (PairSym1 x :: TyFun (g a) (Product f g a) -> Type) #

(SFoldable t, SApplicative f) => SingI1 (For_Sym1 :: t a -> TyFun (a ~> f b) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: t a). Sing x -> Sing (For_Sym1 x :: TyFun (a ~> f b) (f ()) -> Type) #

(STraversable t, SApplicative f) => SingI1 (ForSym1 :: t a -> TyFun (a ~> f b) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: t a). Sing x -> Sing (ForSym1 x :: TyFun (a ~> f b) (f (t b)) -> Type) #

(SFoldable t, SMonad m) => SingI1 (ForM_Sym1 :: t a -> TyFun (a ~> m b) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: t a). Sing x -> Sing (ForM_Sym1 x :: TyFun (a ~> m b) (m ()) -> Type) #

(STraversable t, SMonad m) => SingI1 (ForMSym1 :: t a -> TyFun (a ~> m b) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: t a). Sing x -> Sing (ForMSym1 x :: TyFun (a ~> m b) (m (t b)) -> Type) #

SingI d2 => SingI1 (ZipWith3Sym2 d2 :: [a] -> TyFun [b] ([c] ~> [d1]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWith3Sym2 d2 x) #

(SApplicative m, SingI d) => SingI1 (ZipWithM_Sym2 d :: [a] -> TyFun [b] (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWithM_Sym2 d x) #

(SApplicative m, SingI d) => SingI1 (ZipWithMSym2 d :: [a] -> TyFun [b] (m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWithMSym2 d x) #

(SApplicative f, SingI d) => SingI1 (LiftA2Sym2 d :: f a -> TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (LiftA2Sym2 d x) #

(SMonadZip m, SingI d) => SingI1 (MzipWithSym2 d :: m a -> TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: m a). Sing x -> Sing (MzipWithSym2 d x) #

(SMonad m, SingI d) => SingI1 (LiftM2Sym2 d :: m a1 -> TyFun (m a2) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a1). Sing x -> Sing (LiftM2Sym2 d x) #

(SingI d2, SingI d3) => SingI1 (ZipWith3Sym3 d2 d3 :: [b] -> TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [b]). Sing x -> Sing (ZipWith3Sym3 d2 d3 x) #

(SApplicative f, SingI d2) => SingI1 (LiftA3Sym2 d2 :: f a -> TyFun (f b) (f c ~> f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (LiftA3Sym2 d2 x) #

(SMonad m, SingI d) => SingI1 (LiftM3Sym2 d :: m a1 -> TyFun (m a2) (m a3 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a1). Sing x -> Sing (LiftM3Sym2 d x) #

(SApplicative f, SingI d2, SingI d3) => SingI1 (LiftA3Sym3 d2 d3 :: f b -> TyFun (f c) (f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f b). Sing x -> Sing (LiftA3Sym3 d2 d3 x) #

(SMonad m, SingI d) => SingI1 (LiftM4Sym2 d :: m a1 -> TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a1). Sing x -> Sing (LiftM4Sym2 d x) #

(SMonad m, SingI d1, SingI d2) => SingI1 (LiftM3Sym3 d1 d2 :: m a2 -> TyFun (m a3) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a2). Sing x -> Sing (LiftM3Sym3 d1 d2 x) #

(SMonad m, SingI d) => SingI1 (LiftM5Sym2 d :: m a1 -> TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a1). Sing x -> Sing (LiftM5Sym2 d x) #

(SMonad m, SingI d1, SingI d2) => SingI1 (LiftM4Sym3 d1 d2 :: m a2 -> TyFun (m a3) (m a4 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a2). Sing x -> Sing (LiftM4Sym3 d1 d2 x) #

(SMonad m, SingI d1, SingI d2) => SingI1 (LiftM5Sym3 d1 d2 :: m a2 -> TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a2). Sing x -> Sing (LiftM5Sym3 d1 d2 x) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI1 (LiftM4Sym4 d1 d2 d3 :: m a3 -> TyFun (m a4) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a3). Sing x -> Sing (LiftM4Sym4 d1 d2 d3 x) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI1 (LiftM5Sym4 d1 d2 d3 :: m a3 -> TyFun (m a4) (m a5 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a3). Sing x -> Sing (LiftM5Sym4 d1 d2 d3 x) #

(SMonad m, SingI d1, SingI d2, SingI d3, SingI d4) => SingI1 (LiftM5Sym5 d1 d2 d3 d4 :: m a4 -> TyFun (m a5) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a4). Sing x -> Sing (LiftM5Sym5 d1 d2 d3 d4 x) #

SingI1 ('InL :: f a -> Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ('InL x :: Sum f g a) #

SingI1 ('InR :: g a -> Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

liftSing :: forall (x :: g a). Sing x -> Sing ('InR x :: Sum f g a) #

SingI n => SingI1 ('Pair n :: g a -> Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

liftSing :: forall (x :: g a). Sing x -> Sing ('Pair n x) #

SingI1 ('Compose :: f (g a) -> Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

liftSing :: forall (x :: f (g a)). Sing x -> Sing ('Compose x) #

SingI d => SingI1 (ShowParenSym2 d :: (Symbol ~> Symbol) -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol ~> Symbol). Sing x -> Sing (ShowParenSym2 d x) #

SingI1 (ShowListWithSym1 :: (a ~> (Symbol ~> Symbol)) -> TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a ~> (Symbol ~> Symbol)). Sing x -> Sing (ShowListWithSym1 x) #

SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (SortBySym1 x) #

SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (SortBySym1 x) #

SingI1 (InsertBySym1 :: (a ~> (a ~> Ordering)) -> TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (InsertBySym1 x) #

SingI1 (GroupBy1Sym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (GroupBy1Sym1 x) #

SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (NubBySym1 x) #

SingI1 (DeleteFirstsBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (DeleteFirstsBySym1 x) #

SingI1 (IntersectBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (IntersectBySym1 x) #

SingI1 (UnionBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (UnionBySym1 x) #

SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (GroupBySym1 x) #

SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (GroupBySym1 x) #

SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (NubBySym1 x) #

SingI1 (DeleteBySym1 :: (a ~> (a ~> Bool)) -> TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (DeleteBySym1 x) #

SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanl1Sym1 x) #

SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanr1Sym1 x) #

SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanl1Sym1 x) #

SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanr1Sym1 x) #

SingI1 (Foldl1'Sym1 :: (a ~> (a ~> a)) -> TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Foldl1'Sym1 x) #

SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (BreakSym1 x) #

SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (PartitionSym1 x) #

SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (SpanSym1 x) #

SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (DropWhileSym1 x) #

SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FilterSym1 x) #

SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (TakeWhileSym1 x) #

SingI1 (UntilSym1 :: (a ~> Bool) -> TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (UntilSym1 x) #

SingI1 (FindIndexSym1 :: (a ~> Bool) -> TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FindIndexSym1 x) #

SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (BreakSym1 x) #

SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (PartitionSym1 x) #

SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (SpanSym1 x) #

SingI1 (FindIndicesSym1 :: (a ~> Bool) -> TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FindIndicesSym1 x) #

SingI1 (DropWhileEndSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (DropWhileEndSym1 x) #

SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (DropWhileSym1 x) #

SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FilterSym1 x) #

SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (TakeWhileSym1 x) #

SFoldable t => SingI1 (MaximumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (MaximumBySym1 x :: TyFun (t a) a -> Type) #

SFoldable t => SingI1 (MinimumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (MinimumBySym1 x :: TyFun (t a) a -> Type) #

SFoldable t => SingI1 (Foldl1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Foldl1Sym1 x :: TyFun (t a) a -> Type) #

SFoldable t => SingI1 (Foldr1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Foldr1Sym1 x :: TyFun (t a) a -> Type) #

SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (ScanrSym1 x) #

SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (ScanrSym1 x) #

SingI1 (MapMaybeSym1 :: (a ~> Maybe b) -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: a ~> Maybe b). Sing x -> Sing (MapMaybeSym1 x) #

SingI1 (UnfoldSym1 :: (a ~> (b, Maybe a)) -> TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (b, Maybe a)). Sing x -> Sing (UnfoldSym1 x) #

SingI1 (UnfoldrSym1 :: (a ~> (b, Maybe a)) -> TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (b, Maybe a)). Sing x -> Sing (UnfoldrSym1 x) #

SMonadPlus m => SingI1 (MfilterSym1 :: (a ~> Bool) -> TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (MfilterSym1 x :: TyFun (m a) (m a) -> Type) #

SFoldable t => SingI1 (FindSym1 :: (a ~> Bool) -> TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FindSym1 x :: TyFun (t a) (Maybe a) -> Type) #

SFoldable t => SingI1 (AllSym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (AllSym1 x :: TyFun (t a) Bool -> Type) #

SFoldable t => SingI1 (AnySym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (AnySym1 x :: TyFun (t a) Bool -> Type) #

SingI d => SingI1 (UntilSym2 d :: (a ~> a) -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> a). Sing x -> Sing (UntilSym2 d x) #

SOrd b => SingI1 (GroupAllWith1Sym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (GroupAllWith1Sym1 x) #

SEq b => SingI1 (GroupWith1Sym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (GroupWith1Sym1 x) #

SingI1 (MapSym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (MapSym1 x) #

SOrd b => SingI1 (GroupAllWithSym1 :: (a ~> b) -> TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (GroupAllWithSym1 x) #

SEq b => SingI1 (GroupWithSym1 :: (a ~> b) -> TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (GroupWithSym1 x) #

SingI1 (MapSym1 :: (a ~> b) -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (MapSym1 x) #

SingI1 (($!@#@$$) :: (a ~> b) -> TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (($!@#@$$) x) #

SingI1 (($@#@$$) :: (a ~> b) -> TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (($@#@$$) x) #

SApplicative m => SingI1 (FilterMSym1 :: (a ~> m Bool) -> TyFun [a] (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> m Bool). Sing x -> Sing (FilterMSym1 x) #

SOrd o => SingI1 (SortWithSym1 :: (a ~> o) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> o). Sing x -> Sing (SortWithSym1 x) #

SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (ScanlSym1 x) #

SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (ScanlSym1 x) #

SingI1 (UnfoldrSym1 :: (b ~> Maybe (a, b)) -> TyFun b [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b ~> Maybe (a, b)). Sing x -> Sing (UnfoldrSym1 x) #

SOrd a => SingI1 (ComparingSym1 :: (b ~> a) -> TyFun b (b ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: b ~> a). Sing x -> Sing (ComparingSym1 x) #

SingI1 (CurrySym1 :: ((a, b) ~> c) -> TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: (a, b) ~> c). Sing x -> Sing (CurrySym1 x) #

SFoldable t => SingI1 (Foldr'Sym1 :: (a ~> (b ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (Foldr'Sym1 x :: TyFun b (t a ~> b) -> Type) #

SFoldable t => SingI1 (FoldrSym1 :: (a ~> (b ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (FoldrSym1 x :: TyFun b (t a ~> b) -> Type) #

SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (ZipWithSym1 x) #

SingI1 (UncurrySym1 :: (a ~> (b ~> c)) -> TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (UncurrySym1 x) #

SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (ZipWithSym1 x) #

SingI1 (FlipSym1 :: (a ~> (b ~> c)) -> TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (FlipSym1 x) #

SFoldable t => SingI1 (ConcatMapSym1 :: (a ~> [b]) -> TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> [b]). Sing x -> Sing (ConcatMapSym1 x :: TyFun (t a) [b] -> Type) #

SingI d => SingI1 (Maybe_Sym2 d :: (a ~> b) -> TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (Maybe_Sym2 d x) #

SFunctor f => SingI1 (FmapSym1 :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (FmapSym1 x :: TyFun (f a) (f b) -> Type) #

SApplicative f => SingI1 (LiftASym1 :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (LiftASym1 x :: TyFun (f a) (f b) -> Type) #

SFunctor f => SingI1 ((<$>@#@$$) :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing ((<$>@#@$$) x :: TyFun (f a) (f b) -> Type) #

SMonad m => SingI1 ((<$!>@#@$$) :: (a ~> b) -> TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing ((<$!>@#@$$) x :: TyFun (m a) (m b) -> Type) #

STraversable t => SingI1 (FmapDefaultSym1 :: (a ~> b) -> TyFun (t a) (t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (FmapDefaultSym1 x :: TyFun (t a) (t b) -> Type) #

SingI1 (Either_Sym1 :: (a ~> c) -> TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing :: forall (x :: a ~> c). Sing x -> Sing (Either_Sym1 x :: TyFun (b ~> c) (Either a b ~> c) -> Type) #

(SFoldable t, SMonoid m) => SingI1 (FoldMapSym1 :: (a ~> m) -> TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> m). Sing x -> Sing (FoldMapSym1 x :: TyFun (t a) m -> Type) #

(STraversable t, SMonoid m) => SingI1 (FoldMapDefaultSym1 :: (a ~> m) -> TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> m). Sing x -> Sing (FoldMapDefaultSym1 x :: TyFun (t a) m -> Type) #

SMonad m => SingI1 ((=<<@#@$$) :: (a ~> m b) -> TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing ((=<<@#@$$) x) #

SMonad m => SingI1 (LiftMSym1 :: (a1 ~> r) -> TyFun (m a1) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> r). Sing x -> Sing (LiftMSym1 x :: TyFun (m a1) (m r) -> Type) #

SFoldable t => SingI1 (Foldl'Sym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (Foldl'Sym1 x :: TyFun b (t a ~> b) -> Type) #

SFoldable t => SingI1 (FoldlSym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (FoldlSym1 x :: TyFun b (t a ~> b) -> Type) #

SingI1 (OnSym1 :: (b ~> (b ~> c)) -> TyFun (a ~> b) (a ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing :: forall (x :: b ~> (b ~> c)). Sing x -> Sing (OnSym1 x :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) #

SingI1 ((.@#@$$) :: (b ~> c) -> TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: b ~> c). Sing x -> Sing ((.@#@$$) x :: TyFun (a ~> b) (a ~> c) -> Type) #

SingI1 (ZipWith3Sym1 :: (a ~> (b ~> (c ~> d))) -> TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> (c ~> d))). Sing x -> Sing (ZipWith3Sym1 x) #

STraversable t => SingI1 (MapAccumLSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> (a, c))). Sing x -> Sing (MapAccumLSym1 x :: TyFun a (t b ~> (a, t c)) -> Type) #

STraversable t => SingI1 (MapAccumRSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> (a, c))). Sing x -> Sing (MapAccumRSym1 x :: TyFun a (t b ~> (a, t c)) -> Type) #

SApplicative f => SingI1 (LiftA2Sym1 :: (a ~> (b ~> c)) -> TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (LiftA2Sym1 x :: TyFun (f a) (f b ~> f c) -> Type) #

SMonadZip m => SingI1 (MzipWithSym1 :: (a ~> (b ~> c)) -> TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (MzipWithSym1 x :: TyFun (m a) (m b ~> m c) -> Type) #

(SFoldable t, SMonad m) => SingI1 (FoldrMSym1 :: (a ~> (b ~> m b)) -> TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> m b)). Sing x -> Sing (FoldrMSym1 x :: TyFun b (t a ~> m b) -> Type) #

SApplicative m => SingI1 (ZipWithM_Sym1 :: (a ~> (b ~> m c)) -> TyFun [a] ([b] ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> m c)). Sing x -> Sing (ZipWithM_Sym1 x) #

SApplicative m => SingI1 (ZipWithMSym1 :: (a ~> (b ~> m c)) -> TyFun [a] ([b] ~> m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> m c)). Sing x -> Sing (ZipWithMSym1 x) #

SingI d => SingI1 (OnSym2 d :: (a ~> b) -> TyFun a (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (OnSym2 d x) #

SingI d => SingI1 ((.@#@$$$) d :: (a ~> b) -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (d .@#@$$$ x) #

(SFoldable t, SApplicative f) => SingI1 (Traverse_Sym1 :: (a ~> f b) -> TyFun (t a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> f b). Sing x -> Sing (Traverse_Sym1 x :: TyFun (t a) (f ()) -> Type) #

(STraversable t, SApplicative f) => SingI1 (TraverseSym1 :: (a ~> f b) -> TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> f b). Sing x -> Sing (TraverseSym1 x :: TyFun (t a) (f (t b)) -> Type) #

SApplicative m => SingI1 (MapAndUnzipMSym1 :: (a ~> m (b, c)) -> TyFun [a] (m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> m (b, c)). Sing x -> Sing (MapAndUnzipMSym1 x) #

SMonad m => SingI1 ((>=>@#@$$) :: (a ~> m b) -> TyFun (b ~> m c) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing ((>=>@#@$$) x :: TyFun (b ~> m c) (a ~> m c) -> Type) #

(SFoldable t, SMonad m) => SingI1 (MapM_Sym1 :: (a ~> m b) -> TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing (MapM_Sym1 x :: TyFun (t a) (m ()) -> Type) #

(STraversable t, SMonad m) => SingI1 (MapMSym1 :: (a ~> m b) -> TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing (MapMSym1 x :: TyFun (t a) (m (t b)) -> Type) #

SMonad m => SingI1 (LiftM2Sym1 :: (a1 ~> (a2 ~> r)) -> TyFun (m a1) (m a2 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> (a2 ~> r)). Sing x -> Sing (LiftM2Sym1 x :: TyFun (m a1) (m a2 ~> m r) -> Type) #

(SFoldable t, SMonad m) => SingI1 (FoldlMSym1 :: (b ~> (a ~> m b)) -> TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> m b)). Sing x -> Sing (FoldlMSym1 x :: TyFun b (t a ~> m b) -> Type) #

SingI d => SingI1 (Either_Sym2 d :: (b ~> c) -> TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing :: forall (x :: b ~> c). Sing x -> Sing (Either_Sym2 d x) #

SMonad m => SingI1 ((<=<@#@$$) :: (b ~> m c) -> TyFun (a ~> m b) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: b ~> m c). Sing x -> Sing ((<=<@#@$$) x :: TyFun (a ~> m b) (a ~> m c) -> Type) #

SApplicative f => SingI1 (LiftA3Sym1 :: (a ~> (b ~> (c ~> d))) -> TyFun (f a) (f b ~> (f c ~> f d)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> (c ~> d))). Sing x -> Sing (LiftA3Sym1 x :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) #

(SMonad m, SingI d) => SingI1 ((<=<@#@$$$) d :: (a ~> m b) -> TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing (d <=<@#@$$$ x) #

SMonad m => SingI1 (LiftM3Sym1 :: (a1 ~> (a2 ~> (a3 ~> r))) -> TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> (a2 ~> (a3 ~> r))). Sing x -> Sing (LiftM3Sym1 x :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) #

(SMonad m, SingI d) => SingI1 ((>=>@#@$$$) d :: (b ~> m c) -> TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: b ~> m c). Sing x -> Sing (d >=>@#@$$$ x) #

SMonad m => SingI1 (LiftM4Sym1 :: (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) -> TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))). Sing x -> Sing (LiftM4Sym1 x :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) #

SMonad m => SingI1 (LiftM5Sym1 :: (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) -> TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))). Sing x -> Sing (LiftM5Sym1 x :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) #

class (forall (x :: k1) (y :: k2). (SingI x, SingI y) => SingI (f x y)) => SingI2 (f :: k1 -> k2 -> k3) where #

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (f x y) #

Instances

Instances details
SingI2 ('(:$$:) :: ErrorMessage' Symbol -> ErrorMessage' Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing2 :: forall (x :: PErrorMessage) (y :: PErrorMessage). Sing x -> Sing y -> Sing (x ':$$: y) #

SingI2 ('(:<>:) :: ErrorMessage' Symbol -> ErrorMessage' Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing2 :: forall (x :: PErrorMessage) (y :: PErrorMessage). Sing x -> Sing y -> Sing (x ':<>: y) #

SShow a => SingI2 (ShowsPrecSym2 :: Natural -> a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Natural) (y :: a). Sing x -> Sing y -> Sing (ShowsPrecSym2 x y) #

SingI2 (IfSym2 :: Bool -> k2 -> TyFun k2 k2 -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing2 :: forall (x :: Bool) (y :: k2). Sing x -> Sing y -> Sing (IfSym2 x y) #

SingI2 (Bool_Sym2 :: a -> a -> TyFun Bool a -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing2 :: forall (x :: a) (y :: a). Sing x -> Sing y -> Sing (Bool_Sym2 x y) #

SEnum a => SingI2 (EnumFromThenToSym2 :: a -> a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing2 :: forall (x :: a) (y :: a). Sing x -> Sing y -> Sing (EnumFromThenToSym2 x y) #

SingI2 ('Arg :: k1 -> k2 -> Arg k1 k2) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing ('Arg x y) #

SingI2 ('(,) :: k1 -> k2 -> (k1, k2)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing '(x, y) #

SingI2 (Tuple3Sym2 :: a -> b -> TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple3Sym2 x y :: TyFun c (a, b, c) -> Type) #

SingI2 (Tuple4Sym2 :: a -> b -> TyFun c (d ~> (a, b, c, d)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple4Sym2 x y :: TyFun c (d ~> (a, b, c, d)) -> Type) #

SingI2 (Tuple5Sym2 :: a -> b -> TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple5Sym2 x y :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) #

SingI d1 => SingI2 (Tuple4Sym3 d1 :: b -> c -> TyFun d2 (a, b, c, d2) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple4Sym3 d1 x y :: TyFun d2 (a, b, c, d2) -> Type) #

SingI2 (Tuple6Sym2 :: a -> b -> TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple6Sym2 x y :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) #

SingI d1 => SingI2 (Tuple5Sym3 d1 :: b -> c -> TyFun d2 (e ~> (a, b, c, d2, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple5Sym3 d1 x y :: TyFun d2 (e ~> (a, b, c, d2, e)) -> Type) #

SingI2 (Tuple7Sym2 :: a -> b -> TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple7Sym2 x y :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) #

SingI d1 => SingI2 (Tuple6Sym3 d1 :: b -> c -> TyFun d2 (e ~> (f ~> (a, b, c, d2, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple6Sym3 d1 x y :: TyFun d2 (e ~> (f ~> (a, b, c, d2, e, f))) -> Type) #

(SingI d1, SingI d2) => SingI2 (Tuple5Sym4 d1 d2 :: c -> d3 -> TyFun e (a, b, c, d3, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple5Sym4 d1 d2 x y :: TyFun e (a, b, c, d3, e) -> Type) #

SingI d1 => SingI2 (Tuple7Sym3 d1 :: b -> c -> TyFun d2 (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple7Sym3 d1 x y :: TyFun d2 (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))) -> Type) #

(SingI d1, SingI d2) => SingI2 (Tuple6Sym4 d1 d2 :: c -> d3 -> TyFun e (f ~> (a, b, c, d3, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple6Sym4 d1 d2 x y :: TyFun e (f ~> (a, b, c, d3, e, f)) -> Type) #

(SingI d1, SingI d2) => SingI2 (Tuple7Sym4 d1 d2 :: c -> d3 -> TyFun e (f ~> (g ~> (a, b, c, d3, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple7Sym4 d1 d2 x y :: TyFun e (f ~> (g ~> (a, b, c, d3, e, f, g))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI2 (Tuple6Sym5 d1 d2 d3 :: d4 -> e -> TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: d4) (y :: e). Sing x -> Sing y -> Sing (Tuple6Sym5 d1 d2 d3 x y :: TyFun f (a, b, c, d4, e, f) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI2 (Tuple7Sym5 d1 d2 d3 :: d4 -> e -> TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: d4) (y :: e). Sing x -> Sing y -> Sing (Tuple7Sym5 d1 d2 d3 x y :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI2 (Tuple7Sym6 d1 d2 d3 d5 :: e -> f -> TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: e) (y :: f). Sing x -> Sing y -> Sing (Tuple7Sym6 d1 d2 d3 d5 x y :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

SingI n => SingI2 ('(,,) n :: k1 -> k2 -> (a, k1, k2)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing '(n, x, y) #

(SingI n1, SingI n2) => SingI2 ('(,,,) n1 n2 :: k1 -> k2 -> (a, b, k1, k2)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing '(n1, n2, x, y) #

(SingI n1, SingI n2, SingI n3) => SingI2 ('(,,,,) n1 n2 n3 :: k1 -> k2 -> (a, b, c, k1, k2)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing '(n1, n2, n3, x, y) #

(SingI n1, SingI n2, SingI n3, SingI n4) => SingI2 ('(,,,,,) n1 n2 n3 n4 :: k1 -> k2 -> (a, b, c, d, k1, k2)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing '(n1, n2, n3, n4, x, y) #

(SingI n1, SingI n2, SingI n3, SingI n4, SingI n5) => SingI2 ('(,,,,,,) n1 n2 n3 n4 n5 :: k1 -> k2 -> (a, b, c, d, e, k1, k2)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing '(n1, n2, n3, n4, n5, x, y) #

SingI2 ('(:|) :: k1 -> [k1] -> NonEmpty k1) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: k1) (y :: [k1]). Sing x -> Sing y -> Sing (x ':| y) #

SingI2 ('(:) :: k1 -> [k1] -> [k1]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: k1) (y :: [k1]). Sing x -> Sing y -> Sing (x ': y) #

SingI2 ShowParenSym2 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Bool) (y :: Symbol ~> Symbol). Sing x -> Sing y -> Sing (ShowParenSym2 x y) #

SingI2 (Maybe_Sym2 :: b -> (a ~> b) -> TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing2 :: forall (x :: b) (y :: a ~> b). Sing x -> Sing y -> Sing (Maybe_Sym2 x y) #

SingI2 (Zip3Sym2 :: [a] -> [b] -> TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: [a]) (y :: [b]). Sing x -> Sing y -> Sing (Zip3Sym2 x y :: TyFun [c] [(a, b, c)] -> Type) #

SingI d2 => SingI2 (ZipWith3Sym3 d2 :: [a] -> [b] -> TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: [a]) (y :: [b]). Sing x -> Sing y -> Sing (ZipWith3Sym3 d2 x y) #

(SApplicative f, SingI d2) => SingI2 (LiftA3Sym3 d2 :: f a -> f b -> TyFun (f c) (f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: f a) (y :: f b). Sing x -> Sing y -> Sing (LiftA3Sym3 d2 x y) #

(SMonad m, SingI d) => SingI2 (LiftM3Sym3 d :: m a1 -> m a2 -> TyFun (m a3) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a1) (y :: m a2). Sing x -> Sing y -> Sing (LiftM3Sym3 d x y) #

(SMonad m, SingI d) => SingI2 (LiftM4Sym3 d :: m a1 -> m a2 -> TyFun (m a3) (m a4 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a1) (y :: m a2). Sing x -> Sing y -> Sing (LiftM4Sym3 d x y) #

(SMonad m, SingI d) => SingI2 (LiftM5Sym3 d :: m a1 -> m a2 -> TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a1) (y :: m a2). Sing x -> Sing y -> Sing (LiftM5Sym3 d x y) #

(SMonad m, SingI d1, SingI d2) => SingI2 (LiftM4Sym4 d1 d2 :: m a2 -> m a3 -> TyFun (m a4) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a2) (y :: m a3). Sing x -> Sing y -> Sing (LiftM4Sym4 d1 d2 x y) #

(SMonad m, SingI d1, SingI d2) => SingI2 (LiftM5Sym4 d1 d2 :: m a2 -> m a3 -> TyFun (m a4) (m a5 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a2) (y :: m a3). Sing x -> Sing y -> Sing (LiftM5Sym4 d1 d2 x y) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI2 (LiftM5Sym5 d1 d2 d3 :: m a3 -> m a4 -> TyFun (m a5) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a3) (y :: m a4). Sing x -> Sing y -> Sing (LiftM5Sym5 d1 d2 d3 x y) #

SingI2 ('Pair :: f a -> g a -> Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

liftSing2 :: forall (x :: f a) (y :: g a). Sing x -> Sing y -> Sing ('Pair x y) #

SingI2 (InsertBySym2 :: (a ~> (a ~> Ordering)) -> a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Ordering)) (y :: a). Sing x -> Sing y -> Sing (InsertBySym2 x y) #

SingI2 (DeleteBySym2 :: (a ~> (a ~> Bool)) -> a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Bool)) (y :: a). Sing x -> Sing y -> Sing (DeleteBySym2 x y) #

SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanrSym2 x y) #

SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanrSym2 x y) #

SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanlSym2 x y) #

SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanlSym2 x y) #

SOrd a => SingI2 (ComparingSym2 :: (b ~> a) -> b -> TyFun b Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing2 :: forall (x :: b ~> a) (y :: b). Sing x -> Sing y -> Sing (ComparingSym2 x y) #

SingI2 (CurrySym2 :: ((a, b) ~> c) -> a -> TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing2 :: forall (x :: (a, b) ~> c) (y :: a). Sing x -> Sing y -> Sing (CurrySym2 x y) #

SFoldable t => SingI2 (Foldr'Sym2 :: (a ~> (b ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (Foldr'Sym2 x y :: TyFun (t a) b -> Type) #

SFoldable t => SingI2 (FoldrSym2 :: (a ~> (b ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (FoldrSym2 x y :: TyFun (t a) b -> Type) #

SingI2 (FlipSym2 :: (a ~> (b ~> c)) -> b -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: b). Sing x -> Sing y -> Sing (FlipSym2 x y) #

SFoldable t => SingI2 (Foldl'Sym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (Foldl'Sym2 x y :: TyFun (t a) b -> Type) #

SFoldable t => SingI2 (FoldlSym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (FoldlSym2 x y :: TyFun (t a) b -> Type) #

STraversable t => SingI2 (MapAccumLSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> (a, c))) (y :: a). Sing x -> Sing y -> Sing (MapAccumLSym2 x y :: TyFun (t b) (a, t c) -> Type) #

STraversable t => SingI2 (MapAccumRSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> (a, c))) (y :: a). Sing x -> Sing y -> Sing (MapAccumRSym2 x y :: TyFun (t b) (a, t c) -> Type) #

(SFoldable t, SMonad m) => SingI2 (FoldrMSym2 :: (a ~> (b ~> m b)) -> b -> TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> m b)) (y :: b). Sing x -> Sing y -> Sing (FoldrMSym2 x y :: TyFun (t a) (m b) -> Type) #

SingI d => SingI2 (OnSym3 d :: (a ~> b) -> a -> TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing2 :: forall (x :: a ~> b) (y :: a). Sing x -> Sing y -> Sing (OnSym3 d x y) #

(SFoldable t, SMonad m) => SingI2 (FoldlMSym2 :: (b ~> (a ~> m b)) -> b -> TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> m b)) (y :: b). Sing x -> Sing y -> Sing (FoldlMSym2 x y :: TyFun (t a) (m b) -> Type) #

SingI2 (ShowListWithSym2 :: (a ~> (Symbol ~> Symbol)) -> [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: a ~> (Symbol ~> Symbol)) (y :: [a]). Sing x -> Sing y -> Sing (ShowListWithSym2 x y) #

SingI2 (DeleteFirstsBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Bool)) (y :: [a]). Sing x -> Sing y -> Sing (DeleteFirstsBySym2 x y) #

SingI2 (IntersectBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Bool)) (y :: [a]). Sing x -> Sing y -> Sing (IntersectBySym2 x y) #

SingI2 (UnionBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Bool)) (y :: [a]). Sing x -> Sing y -> Sing (UnionBySym2 x y) #

SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> NonEmpty a -> TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: NonEmpty a). Sing x -> Sing y -> Sing (ZipWithSym2 x y) #

SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> [a] -> TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: [a]). Sing x -> Sing y -> Sing (ZipWithSym2 x y) #

SingI2 (ZipWith3Sym2 :: (a ~> (b ~> (c ~> d))) -> [a] -> TyFun [b] ([c] ~> [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> (c ~> d))) (y :: [a]). Sing x -> Sing y -> Sing (ZipWith3Sym2 x y) #

SApplicative f => SingI2 (LiftA2Sym2 :: (a ~> (b ~> c)) -> f a -> TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: f a). Sing x -> Sing y -> Sing (LiftA2Sym2 x y) #

SMonadZip m => SingI2 (MzipWithSym2 :: (a ~> (b ~> c)) -> m a -> TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: m a). Sing x -> Sing y -> Sing (MzipWithSym2 x y) #

SApplicative m => SingI2 (ZipWithM_Sym2 :: (a ~> (b ~> m c)) -> [a] -> TyFun [b] (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> m c)) (y :: [a]). Sing x -> Sing y -> Sing (ZipWithM_Sym2 x y) #

SApplicative m => SingI2 (ZipWithMSym2 :: (a ~> (b ~> m c)) -> [a] -> TyFun [b] (m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> m c)) (y :: [a]). Sing x -> Sing y -> Sing (ZipWithMSym2 x y) #

SMonad m => SingI2 (LiftM2Sym2 :: (a1 ~> (a2 ~> r)) -> m a1 -> TyFun (m a2) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a1 ~> (a2 ~> r)) (y :: m a1). Sing x -> Sing y -> Sing (LiftM2Sym2 x y) #

SApplicative f => SingI2 (LiftA3Sym2 :: (a ~> (b ~> (c ~> d))) -> f a -> TyFun (f b) (f c ~> f d) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> (c ~> d))) (y :: f a). Sing x -> Sing y -> Sing (LiftA3Sym2 x y) #

SMonad m => SingI2 (LiftM3Sym2 :: (a1 ~> (a2 ~> (a3 ~> r))) -> m a1 -> TyFun (m a2) (m a3 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a1 ~> (a2 ~> (a3 ~> r))) (y :: m a1). Sing x -> Sing y -> Sing (LiftM3Sym2 x y) #

SMonad m => SingI2 (LiftM4Sym2 :: (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) -> m a1 -> TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (y :: m a1). Sing x -> Sing y -> Sing (LiftM4Sym2 x y) #

SMonad m => SingI2 (LiftM5Sym2 :: (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) -> m a1 -> TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (y :: m a1). Sing x -> Sing y -> Sing (LiftM5Sym2 x y) #

SingI2 (UntilSym2 :: (a ~> Bool) -> (a ~> a) -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: a ~> Bool) (y :: a ~> a). Sing x -> Sing y -> Sing (UntilSym2 x y) #

SingI2 (Either_Sym2 :: (a ~> c) -> (b ~> c) -> TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing2 :: forall (x :: a ~> c) (y :: b ~> c). Sing x -> Sing y -> Sing (Either_Sym2 x y) #

SingI2 (OnSym2 :: (b ~> (b ~> c)) -> (a ~> b) -> TyFun a (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing2 :: forall (x :: b ~> (b ~> c)) (y :: a ~> b). Sing x -> Sing y -> Sing (OnSym2 x y) #

SingI2 ((.@#@$$$) :: (b ~> c) -> (a ~> b) -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: b ~> c) (y :: a ~> b). Sing x -> Sing y -> Sing (x .@#@$$$ y) #

SMonad m => SingI2 ((>=>@#@$$$) :: (a ~> m b) -> (b ~> m c) -> TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing2 :: forall (x :: a ~> m b) (y :: b ~> m c). Sing x -> Sing y -> Sing (x >=>@#@$$$ y) #

SMonad m => SingI2 ((<=<@#@$$$) :: (b ~> m c) -> (a ~> m b) -> TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing2 :: forall (x :: b ~> m c) (y :: a ~> m b). Sing x -> Sing y -> Sing (x <=<@#@$$$ y) #

data SingInstance (a :: k) where #

Constructors

SingInstance :: forall {k} (a :: k). SingI a => SingInstance a 

class SingKind k where #

Associated Types

type Demote k = (r :: Type) | r -> k #

Methods

fromSing :: forall (a :: k). Sing a -> Demote k #

toSing :: Demote k -> SomeSing k #

Instances

Instances details
SingKind Void Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote Void 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

fromSing :: forall (a :: Void). Sing a -> Demote Void #

toSing :: Demote Void -> SomeSing Void #

SingKind All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote All 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote All = All

Methods

fromSing :: forall (a :: All). Sing a -> Demote All #

toSing :: Demote All -> SomeSing All #

SingKind Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote Any 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote Any = Any

Methods

fromSing :: forall (a :: Any). Sing a -> Demote Any #

toSing :: Demote Any -> SomeSing Any #

SingKind Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote Ordering 
Instance details

Defined in Data.Singletons.Base.Instances

SingKind PErrorMessage Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Associated Types

type Demote PErrorMessage 
Instance details

Defined in Data.Singletons.Base.TypeError

SingKind Natural Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type Demote Natural 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

fromSing :: forall (a :: Natural). Sing a -> Demote Natural #

toSing :: Demote Natural -> SomeSing Natural #

SingKind () Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote () 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote () = ()

Methods

fromSing :: forall (a :: ()). Sing a -> Demote () #

toSing :: Demote () -> SomeSing () #

SingKind Bool Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote Bool 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

fromSing :: forall (a :: Bool). Sing a -> Demote Bool #

toSing :: Demote Bool -> SomeSing Bool #

SingKind Char Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type Demote Char 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

fromSing :: forall (a :: Char). Sing a -> Demote Char #

toSing :: Demote Char -> SomeSing Char #

SingKind Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type Demote Symbol 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

fromSing :: forall (a :: Symbol). Sing a -> Demote Symbol #

toSing :: Demote Symbol -> SomeSing Symbol #

SingKind a => SingKind (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote (First a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (First a) = First (Demote a)

Methods

fromSing :: forall (a0 :: First a). Sing a0 -> Demote (First a) #

toSing :: Demote (First a) -> SomeSing (First a) #

SingKind a => SingKind (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote (Last a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Last a) = Last (Demote a)

Methods

fromSing :: forall (a0 :: Last a). Sing a0 -> Demote (Last a) #

toSing :: Demote (Last a) -> SomeSing (Last a) #

SingKind a => SingKind (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote (Max a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Max a) = Max (Demote a)

Methods

fromSing :: forall (a0 :: Max a). Sing a0 -> Demote (Max a) #

toSing :: Demote (Max a) -> SomeSing (Max a) #

SingKind a => SingKind (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote (Min a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Min a) = Min (Demote a)

Methods

fromSing :: forall (a0 :: Min a). Sing a0 -> Demote (Min a) #

toSing :: Demote (Min a) -> SomeSing (Min a) #

SingKind m => SingKind (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote (WrappedMonoid m) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SingKind a => SingKind (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (NonEmpty a) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

fromSing :: forall (a0 :: NonEmpty a). Sing a0 -> Demote (NonEmpty a) #

toSing :: Demote (NonEmpty a) -> SomeSing (NonEmpty a) #

SingKind a => SingKind (Identity a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (Identity a) 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

fromSing :: forall (a0 :: Identity a). Sing a0 -> Demote (Identity a) #

toSing :: Demote (Identity a) -> SomeSing (Identity a) #

SingKind a => SingKind (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Demote (First a) 
Instance details

Defined in Data.Monoid.Singletons

type Demote (First a) = First (Demote a)

Methods

fromSing :: forall (a0 :: First a). Sing a0 -> Demote (First a) #

toSing :: Demote (First a) -> SomeSing (First a) #

SingKind a => SingKind (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Demote (Last a) 
Instance details

Defined in Data.Monoid.Singletons

type Demote (Last a) = Last (Demote a)

Methods

fromSing :: forall (a0 :: Last a). Sing a0 -> Demote (Last a) #

toSing :: Demote (Last a) -> SomeSing (Last a) #

SingKind a => SingKind (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type Demote (Down a) 
Instance details

Defined in Data.Ord.Singletons

type Demote (Down a) = Down (Demote a)

Methods

fromSing :: forall (a0 :: Down a). Sing a0 -> Demote (Down a) #

toSing :: Demote (Down a) -> SomeSing (Down a) #

SingKind a => SingKind (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote (Dual a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Dual a) = Dual (Demote a)

Methods

fromSing :: forall (a0 :: Dual a). Sing a0 -> Demote (Dual a) #

toSing :: Demote (Dual a) -> SomeSing (Dual a) #

SingKind a => SingKind (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote (Product a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Product a) = Product (Demote a)

Methods

fromSing :: forall (a0 :: Product a). Sing a0 -> Demote (Product a) #

toSing :: Demote (Product a) -> SomeSing (Product a) #

SingKind a => SingKind (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Demote (Sum a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Demote (Sum a) = Sum (Demote a)

Methods

fromSing :: forall (a0 :: Sum a). Sing a0 -> Demote (Sum a) #

toSing :: Demote (Sum a) -> SomeSing (Sum a) #

SingKind a => SingKind (Maybe a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (Maybe a) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (Maybe a) = Maybe (Demote a)

Methods

fromSing :: forall (a0 :: Maybe a). Sing a0 -> Demote (Maybe a) #

toSing :: Demote (Maybe a) -> SomeSing (Maybe a) #

SingKind (TYPE rep) Source # 
Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

Associated Types

type Demote (TYPE rep) 
Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

type Demote (TYPE rep) = SomeTypeRepTYPE rep

Methods

fromSing :: forall (a :: TYPE rep). Sing a -> Demote (TYPE rep) #

toSing :: Demote (TYPE rep) -> SomeSing (TYPE rep) #

SingKind a => SingKind [a] Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote [a] 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote [a] = [Demote a]

Methods

fromSing :: forall (a0 :: [a]). Sing a0 -> Demote [a] #

toSing :: Demote [a] -> SomeSing [a] #

(SingKind a, SingKind b) => SingKind (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Demote (Arg a b) 
Instance details

Defined in Data.Semigroup.Singletons

type Demote (Arg a b) = Arg (Demote a) (Demote b)

Methods

fromSing :: forall (a0 :: Arg a b). Sing a0 -> Demote (Arg a b) #

toSing :: Demote (Arg a b) -> SomeSing (Arg a b) #

(SingKind a, SingKind b) => SingKind (Either a b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (Either a b) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (Either a b) = Either (Demote a) (Demote b)

Methods

fromSing :: forall (a0 :: Either a b). Sing a0 -> Demote (Either a b) #

toSing :: Demote (Either a b) -> SomeSing (Either a b) #

SingKind (Proxy t) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Demote (Proxy t) 
Instance details

Defined in Data.Proxy.Singletons

type Demote (Proxy t) = Proxy t

Methods

fromSing :: forall (a :: Proxy t). Sing a -> Demote (Proxy t) #

toSing :: Demote (Proxy t) -> SomeSing (Proxy t) #

SingKind (WrappedSing a) # 
Instance details

Defined in Data.Singletons

Associated Types

type Demote (WrappedSing a) 
Instance details

Defined in Data.Singletons

Methods

fromSing :: forall (a0 :: WrappedSing a). Sing a0 -> Demote (WrappedSing a) #

toSing :: Demote (WrappedSing a) -> SomeSing (WrappedSing a) #

(SingKind k1, SingKind k2) => SingKind (k1 ~> k2) # 
Instance details

Defined in Data.Singletons

Associated Types

type Demote (k1 ~> k2) 
Instance details

Defined in Data.Singletons

type Demote (k1 ~> k2) = Demote k1 -> Demote k2

Methods

fromSing :: forall (a :: k1 ~> k2). Sing a -> Demote (k1 ~> k2) #

toSing :: Demote (k1 ~> k2) -> SomeSing (k1 ~> k2) #

(SingKind a, SingKind b) => SingKind (a, b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (a, b) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b) = (Demote a, Demote b)

Methods

fromSing :: forall (a0 :: (a, b)). Sing a0 -> Demote (a, b) #

toSing :: Demote (a, b) -> SomeSing (a, b) #

SingKind a => SingKind (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Associated Types

type Demote (Const a b) 
Instance details

Defined in Data.Functor.Const.Singletons

type Demote (Const a b) = Const (Demote a) b

Methods

fromSing :: forall (a0 :: Const a b). Sing a0 -> Demote (Const a b) #

toSing :: Demote (Const a b) -> SomeSing (Const a b) #

(SingKind a, SingKind b, SingKind c) => SingKind (a, b, c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (a, b, c) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c) = (Demote a, Demote b, Demote c)

Methods

fromSing :: forall (a0 :: (a, b, c)). Sing a0 -> Demote (a, b, c) #

toSing :: Demote (a, b, c) -> SomeSing (a, b, c) #

(SingKind a, SingKind b, SingKind c, SingKind d) => SingKind (a, b, c, d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (a, b, c, d) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c, d) = (Demote a, Demote b, Demote c, Demote d)

Methods

fromSing :: forall (a0 :: (a, b, c, d)). Sing a0 -> Demote (a, b, c, d) #

toSing :: Demote (a, b, c, d) -> SomeSing (a, b, c, d) #

(SingKind a, SingKind b, SingKind c, SingKind d, SingKind e) => SingKind (a, b, c, d, e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (a, b, c, d, e) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c, d, e) = (Demote a, Demote b, Demote c, Demote d, Demote e)

Methods

fromSing :: forall (a0 :: (a, b, c, d, e)). Sing a0 -> Demote (a, b, c, d, e) #

toSing :: Demote (a, b, c, d, e) -> SomeSing (a, b, c, d, e) #

(SingKind a, SingKind b, SingKind c, SingKind d, SingKind e, SingKind f) => SingKind (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (a, b, c, d, e, f) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c, d, e, f) = (Demote a, Demote b, Demote c, Demote d, Demote e, Demote f)

Methods

fromSing :: forall (a0 :: (a, b, c, d, e, f)). Sing a0 -> Demote (a, b, c, d, e, f) #

toSing :: Demote (a, b, c, d, e, f) -> SomeSing (a, b, c, d, e, f) #

(SingKind a, SingKind b, SingKind c, SingKind d, SingKind e, SingKind f, SingKind g) => SingKind (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Associated Types

type Demote (a, b, c, d, e, f, g) 
Instance details

Defined in Data.Singletons.Base.Instances

type Demote (a, b, c, d, e, f, g) = (Demote a, Demote b, Demote c, Demote d, Demote e, Demote f, Demote g)

Methods

fromSing :: forall (a0 :: (a, b, c, d, e, f, g)). Sing a0 -> Demote (a, b, c, d, e, f, g) #

toSing :: Demote (a, b, c, d, e, f, g) -> SomeSing (a, b, c, d, e, f, g) #

data SomeSing k where #

Constructors

SomeSing :: forall k (a :: k). Sing a -> SomeSing k 

Instances

Instances details
SMonoid k => Monoid (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

Methods

mempty :: SomeSing k #

mappend :: SomeSing k -> SomeSing k -> SomeSing k #

mconcat :: [SomeSing k] -> SomeSing k #

SSemigroup k => Semigroup (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

Methods

(<>) :: SomeSing k -> SomeSing k -> SomeSing k #

sconcat :: NonEmpty (SomeSing k) -> SomeSing k #

stimes :: Integral b => b -> SomeSing k -> SomeSing k #

SIsString k => IsString (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

Methods

fromString :: String -> SomeSing k #

SBounded k => Bounded (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

SEnum k => Enum (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

SNum k => Num (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

ShowSing k => Show (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

Methods

showsPrec :: Int -> SomeSing k -> ShowS #

show :: SomeSing k -> String #

showList :: [SomeSing k] -> ShowS #

SEq k => Eq (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

Methods

(==) :: SomeSing k -> SomeSing k -> Bool #

(/=) :: SomeSing k -> SomeSing k -> Bool #

SOrd k => Ord (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

Methods

compare :: SomeSing k -> SomeSing k -> Ordering #

(<) :: SomeSing k -> SomeSing k -> Bool #

(<=) :: SomeSing k -> SomeSing k -> Bool #

(>) :: SomeSing k -> SomeSing k -> Bool #

(>=) :: SomeSing k -> SomeSing k -> Bool #

max :: SomeSing k -> SomeSing k -> SomeSing k #

min :: SomeSing k -> SomeSing k -> SomeSing k #

data family TyCon :: forall k1 k2 unmatchable_fun. (k1 -> k2) -> unmatchable_fun #

Instances

Instances details
(forall (a :: k1). SingI a => SingI (f a), (ApplyTyCon :: (k1 -> kr) -> TyFun k1 kr -> Type) ~ (ApplyTyConAux1 :: (k1 -> kr) -> TyFun k1 kr -> Type)) => SingI (TyCon1 f :: TyFun k1 kr -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon1 f) #

(forall (a :: k1) (b :: k2). (SingI a, SingI b) => SingI (f a b), (ApplyTyCon :: (k2 -> kr) -> TyFun k2 kr -> Type) ~ (ApplyTyConAux1 :: (k2 -> kr) -> TyFun k2 kr -> Type)) => SingI (TyCon2 f :: TyFun k1 (k2 ~> kr) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon2 f) #

(forall (a :: k1) (b :: k2) (c :: k3). (SingI a, SingI b, SingI c) => SingI (f a b c), (ApplyTyCon :: (k3 -> kr) -> TyFun k3 kr -> Type) ~ (ApplyTyConAux1 :: (k3 -> kr) -> TyFun k3 kr -> Type)) => SingI (TyCon3 f :: TyFun k1 (k2 ~> (k3 ~> kr)) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon3 f) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4). (SingI a, SingI b, SingI c, SingI d) => SingI (f a b c d), (ApplyTyCon :: (k4 -> kr) -> TyFun k4 kr -> Type) ~ (ApplyTyConAux1 :: (k4 -> kr) -> TyFun k4 kr -> Type)) => SingI (TyCon4 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> kr))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon4 f) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5). (SingI a, SingI b, SingI c, SingI d, SingI e) => SingI (f a b c d e), (ApplyTyCon :: (k5 -> kr) -> TyFun k5 kr -> Type) ~ (ApplyTyConAux1 :: (k5 -> kr) -> TyFun k5 kr -> Type)) => SingI (TyCon5 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> kr)))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon5 f) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f') => SingI (f a b c d e f'), (ApplyTyCon :: (k6 -> kr) -> TyFun k6 kr -> Type) ~ (ApplyTyConAux1 :: (k6 -> kr) -> TyFun k6 kr -> Type)) => SingI (TyCon6 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> kr))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon6 f) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6) (g :: k7). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f', SingI g) => SingI (f a b c d e f' g), (ApplyTyCon :: (k7 -> kr) -> TyFun k7 kr -> Type) ~ (ApplyTyConAux1 :: (k7 -> kr) -> TyFun k7 kr -> Type)) => SingI (TyCon7 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> kr)))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon7 f) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6) (g :: k7) (h :: k8). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f', SingI g, SingI h) => SingI (f a b c d e f' g h), (ApplyTyCon :: (k8 -> kr) -> TyFun k8 kr -> Type) ~ (ApplyTyConAux1 :: (k8 -> kr) -> TyFun k8 kr -> Type)) => SingI (TyCon8 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k8 ~> kr))))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon8 f) #

type Apply (TyCon f :: k1 ~> k3) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply (TyCon f :: k1 ~> k3) (x :: k1) = ApplyTyCon f @@ x

type TyCon1 = TyCon #

type TyCon2 = TyCon #

type TyCon3 = TyCon #

type TyCon4 = TyCon #

type TyCon5 = TyCon #

type TyCon6 = TyCon #

type TyCon7 = TyCon #

type TyCon8 = TyCon #

data TyFun a b #

Instances

Instances details
SShow a => SingI2 (ShowsPrecSym2 :: Natural -> a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Natural) (y :: a). Sing x -> Sing y -> Sing (ShowsPrecSym2 x y) #

SingI2 (IfSym2 :: Bool -> k2 -> TyFun k2 k2 -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing2 :: forall (x :: Bool) (y :: k2). Sing x -> Sing y -> Sing (IfSym2 x y) #

SingI2 (Bool_Sym2 :: a -> a -> TyFun Bool a -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing2 :: forall (x :: a) (y :: a). Sing x -> Sing y -> Sing (Bool_Sym2 x y) #

SEnum a => SingI2 (EnumFromThenToSym2 :: a -> a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing2 :: forall (x :: a) (y :: a). Sing x -> Sing y -> Sing (EnumFromThenToSym2 x y) #

SingI2 (Tuple3Sym2 :: a -> b -> TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple3Sym2 x y :: TyFun c (a, b, c) -> Type) #

SingI2 (Tuple4Sym2 :: a -> b -> TyFun c (d ~> (a, b, c, d)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple4Sym2 x y :: TyFun c (d ~> (a, b, c, d)) -> Type) #

SingI2 (Tuple5Sym2 :: a -> b -> TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple5Sym2 x y :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) #

SingI d1 => SingI2 (Tuple4Sym3 d1 :: b -> c -> TyFun d2 (a, b, c, d2) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple4Sym3 d1 x y :: TyFun d2 (a, b, c, d2) -> Type) #

SingI2 (Tuple6Sym2 :: a -> b -> TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple6Sym2 x y :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) #

SingI d1 => SingI2 (Tuple5Sym3 d1 :: b -> c -> TyFun d2 (e ~> (a, b, c, d2, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple5Sym3 d1 x y :: TyFun d2 (e ~> (a, b, c, d2, e)) -> Type) #

SingI2 (Tuple7Sym2 :: a -> b -> TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple7Sym2 x y :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) #

SingI d1 => SingI2 (Tuple6Sym3 d1 :: b -> c -> TyFun d2 (e ~> (f ~> (a, b, c, d2, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple6Sym3 d1 x y :: TyFun d2 (e ~> (f ~> (a, b, c, d2, e, f))) -> Type) #

(SingI d1, SingI d2) => SingI2 (Tuple5Sym4 d1 d2 :: c -> d3 -> TyFun e (a, b, c, d3, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple5Sym4 d1 d2 x y :: TyFun e (a, b, c, d3, e) -> Type) #

SingI d1 => SingI2 (Tuple7Sym3 d1 :: b -> c -> TyFun d2 (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple7Sym3 d1 x y :: TyFun d2 (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))) -> Type) #

(SingI d1, SingI d2) => SingI2 (Tuple6Sym4 d1 d2 :: c -> d3 -> TyFun e (f ~> (a, b, c, d3, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple6Sym4 d1 d2 x y :: TyFun e (f ~> (a, b, c, d3, e, f)) -> Type) #

(SingI d1, SingI d2) => SingI2 (Tuple7Sym4 d1 d2 :: c -> d3 -> TyFun e (f ~> (g ~> (a, b, c, d3, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple7Sym4 d1 d2 x y :: TyFun e (f ~> (g ~> (a, b, c, d3, e, f, g))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI2 (Tuple6Sym5 d1 d2 d3 :: d4 -> e -> TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: d4) (y :: e). Sing x -> Sing y -> Sing (Tuple6Sym5 d1 d2 d3 x y :: TyFun f (a, b, c, d4, e, f) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI2 (Tuple7Sym5 d1 d2 d3 :: d4 -> e -> TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: d4) (y :: e). Sing x -> Sing y -> Sing (Tuple7Sym5 d1 d2 d3 x y :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI2 (Tuple7Sym6 d1 d2 d3 d5 :: e -> f -> TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: e) (y :: f). Sing x -> Sing y -> Sing (Tuple7Sym6 d1 d2 d3 d5 x y :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

SingI1 DivSym1 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (DivSym1 x) #

SingI1 ModSym1 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ModSym1 x) #

SingI1 (^@#@$$) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing ((^@#@$$) x) #

SingI1 ShowParenSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (ShowParenSym1 x) #

SingI1 ShowCharSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Char). Sing x -> Sing (ShowCharSym1 x) #

SingI1 ConsSymbolSym1 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

liftSing :: forall (x :: Char). Sing x -> Sing (ConsSymbolSym1 x) #

SingI1 ShowStringSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol). Sing x -> Sing (ShowStringSym1 x) #

SingI1 ((:$$:@#@$$) :: ErrorMessage' Symbol -> TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing ((:$$:@#@$$) x) #

SingI1 ((:<>:@#@$$) :: ErrorMessage' Symbol -> TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing ((:<>:@#@$$) x) #

SingI1 (SplitAtSym1 :: Natural -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (SplitAtSym1 x :: TyFun (NonEmpty a) ([a], [a]) -> Type) #

SingI1 (DropSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (DropSym1 x :: TyFun (NonEmpty a) [a] -> Type) #

SingI1 (TakeSym1 :: Natural -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (TakeSym1 x :: TyFun (NonEmpty a) [a] -> Type) #

SingI1 (SplitAtSym1 :: Natural -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (SplitAtSym1 x :: TyFun [a] ([a], [a]) -> Type) #

SingI1 (DropSym1 :: Natural -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (DropSym1 x :: TyFun [a] [a] -> Type) #

SingI1 (TakeSym1 :: Natural -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (TakeSym1 x :: TyFun [a] [a] -> Type) #

SShow a => SingI1 (ShowsPrecSym1 :: Natural -> TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ShowsPrecSym1 x :: TyFun a (Symbol ~> Symbol) -> Type) #

SingI1 (ReplicateSym1 :: Natural -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ReplicateSym1 x :: TyFun a [a] -> Type) #

SingI1 ((<=?@#@$$) :: Natural -> TyFun Natural Bool -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing ((<=?@#@$$) x) #

SApplicative f => SingI1 (UnlessSym1 :: Bool -> TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (UnlessSym1 x :: TyFun (f ()) (f ()) -> Type) #

SApplicative f => SingI1 (WhenSym1 :: Bool -> TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (WhenSym1 x :: TyFun (f ()) (f ()) -> Type) #

SingI1 (IfSym1 :: Bool -> TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (IfSym1 x :: TyFun k (k ~> k) -> Type) #

SingI1 ((<|@#@$$) :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<|@#@$$) x) #

SingI1 (ConsSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ConsSym1 x) #

SingI1 (IntersperseSym1 :: a -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (IntersperseSym1 x) #

SingI1 (FromMaybeSym1 :: a -> TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (FromMaybeSym1 x) #

SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (InsertSym1 x) #

SingI1 ((:|@#@$$) :: a -> TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((:|@#@$$) x) #

SEq a => SingI1 (ElemIndexSym1 :: a -> TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ElemIndexSym1 x) #

SEq a => SingI1 (ElemIndicesSym1 :: a -> TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ElemIndicesSym1 x) #

SEq a => SingI1 (DeleteSym1 :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (DeleteSym1 x) #

SOrd a => SingI1 (InsertSym1 :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (InsertSym1 x) #

SingI1 (IntersperseSym1 :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (IntersperseSym1 x) #

SingI1 ((:@#@$$) :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((:@#@$$) x) #

SShow a => SingI1 (ShowsSym1 :: a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsSym1 x) #

SOrd a => SingI1 (CompareSym1 :: a -> TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (CompareSym1 x) #

SingI1 (Bool_Sym1 :: a -> TyFun a (Bool ~> a) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Bool_Sym1 x) #

SEnum a => SingI1 (EnumFromThenToSym1 :: a -> TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromThenToSym1 x) #

SEq a => SingI1 ((/=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((/=@#@$$) x) #

SEq a => SingI1 ((==@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((==@#@$$) x) #

SOrd a => SingI1 ((<=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<=@#@$$) x) #

SOrd a => SingI1 ((<@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<@#@$$) x) #

SOrd a => SingI1 ((>=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((>=@#@$$) x) #

SOrd a => SingI1 ((>@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((>@#@$$) x) #

SEnum a => SingI1 (EnumFromToSym1 :: a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromToSym1 x) #

SMonoid a => SingI1 (MappendSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MappendSym1 x) #

SOrd a => SingI1 (MaxSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MaxSym1 x) #

SOrd a => SingI1 (MinSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MinSym1 x) #

SSemigroup a => SingI1 ((<>@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<>@#@$$) x) #

SingI1 (AsTypeOfSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (AsTypeOfSym1 x) #

SNum a => SingI1 ((*@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((*@#@$$) x) #

SNum a => SingI1 ((+@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((+@#@$$) x) #

SNum a => SingI1 ((-@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((-@#@$$) x) #

SNum a => SingI1 (SubtractSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (SubtractSym1 x) #

SApplicative m => SingI1 (ReplicateM_Sym1 :: Natural -> TyFun (m a) (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ReplicateM_Sym1 x :: TyFun (m a) (m ()) -> Type) #

SApplicative m => SingI1 (ReplicateMSym1 :: Natural -> TyFun (m a) (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ReplicateMSym1 x :: TyFun (m a) (m [a]) -> Type) #

SingI1 ((&@#@$$) :: a -> TyFun (a ~> b) b -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((&@#@$$) x :: TyFun (a ~> b) b -> Type) #

SingI d => SingI1 (Bool_Sym2 d :: a -> TyFun Bool a -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Bool_Sym2 d x) #

SEq a => SingI1 (LookupSym1 :: a -> TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (LookupSym1 x :: TyFun [(a, b)] (Maybe b) -> Type) #

SingI d => SingI1 (DeleteBySym2 d :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (DeleteBySym2 d x) #

SingI d => SingI1 (InsertBySym2 d :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (InsertBySym2 d x) #

(SShow a, SingI d) => SingI1 (ShowsPrecSym2 d :: a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsPrecSym2 d x) #

(SEnum a, SingI d) => SingI1 (EnumFromThenToSym2 d :: a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromThenToSym2 d x) #

SingI1 (ArgSym1 :: a -> TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ArgSym1 x :: TyFun b (Arg a b) -> Type) #

SingI1 (Tuple2Sym1 :: a -> TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple2Sym1 x :: TyFun b (a, b) -> Type) #

SingI1 (ConstSym1 :: a -> TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ConstSym1 x :: TyFun b a -> Type) #

SingI1 (SeqSym1 :: a -> TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (SeqSym1 x :: TyFun b b -> Type) #

SingI1 (AsProxyTypeOfSym1 :: a -> TyFun (proxy a) a -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (AsProxyTypeOfSym1 x :: TyFun (proxy a) a -> Type) #

(SFoldable t, SEq a) => SingI1 (ElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ElemSym1 x :: TyFun (t a) Bool -> Type) #

(SFoldable t, SEq a) => SingI1 (NotElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (NotElemSym1 x :: TyFun (t a) Bool -> Type) #

SingI1 (Maybe_Sym1 :: b -> TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Maybe_Sym1 x :: TyFun (a ~> b) (Maybe a ~> b) -> Type) #

SingI c => SingI1 (IfSym2 c :: k1 -> TyFun k1 k1 -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (IfSym2 c x) #

SingI2 ShowParenSym2 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Bool) (y :: Symbol ~> Symbol). Sing x -> Sing y -> Sing (ShowParenSym2 x y) #

SingI2 (Maybe_Sym2 :: b -> (a ~> b) -> TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing2 :: forall (x :: b) (y :: a ~> b). Sing x -> Sing y -> Sing (Maybe_Sym2 x y) #

SingI1 (Tuple3Sym1 :: a -> TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple3Sym1 x :: TyFun b (c ~> (a, b, c)) -> Type) #

SFunctor f => SingI1 ((<$@#@$$) :: a -> TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<$@#@$$) x :: TyFun (f b) (f a) -> Type) #

SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanlSym2 d x) #

SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanrSym2 d x) #

SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanlSym2 d x) #

SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanrSym2 d x) #

(SOrd a, SingI d) => SingI1 (ComparingSym2 d :: b -> TyFun b Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ComparingSym2 d x) #

SingI1 (Tuple4Sym1 :: a -> TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple4Sym1 x :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) #

SingI d => SingI1 (CurrySym2 d :: a -> TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (CurrySym2 d x) #

SingI d => SingI1 (FlipSym2 d :: b -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FlipSym2 d x) #

SingI d => SingI1 (Tuple3Sym2 d :: b -> TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple3Sym2 d x :: TyFun c (a, b, c) -> Type) #

(SFoldable t, SingI d) => SingI1 (Foldl'Sym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Foldl'Sym2 d x :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d) => SingI1 (FoldlSym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldlSym2 d x :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d) => SingI1 (Foldr'Sym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Foldr'Sym2 d x :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d) => SingI1 (FoldrSym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldrSym2 d x :: TyFun (t a) b -> Type) #

(SingI d1, SingI d2) => SingI1 (OnSym3 d1 d2 :: a -> TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (OnSym3 d1 d2 x) #

SingI1 (Tuple5Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple5Sym1 x :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) #

(STraversable t, SingI d) => SingI1 (MapAccumLSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MapAccumLSym2 d x :: TyFun (t b) (a, t c) -> Type) #

(STraversable t, SingI d) => SingI1 (MapAccumRSym2 d :: a -> TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MapAccumRSym2 d x :: TyFun (t b) (a, t c) -> Type) #

SingI d1 => SingI1 (Tuple4Sym2 d1 :: b -> TyFun c (d2 ~> (a, b, c, d2)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple4Sym2 d1 x :: TyFun c (d2 ~> (a, b, c, d2)) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI1 (FoldlMSym2 d :: b -> TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldlMSym2 d x :: TyFun (t a) (m b) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI1 (FoldrMSym2 d :: b -> TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldrMSym2 d x :: TyFun (t a) (m b) -> Type) #

SingI1 (Tuple6Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple6Sym1 x :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) #

SingI d1 => SingI1 (Tuple5Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (a, b, c, d2, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple5Sym2 d1 x :: TyFun c (d2 ~> (e ~> (a, b, c, d2, e))) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple4Sym3 d1 d2 :: c -> TyFun d3 (a, b, c, d3) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple4Sym3 d1 d2 x :: TyFun d3 (a, b, c, d3) -> Type) #

SingI1 (Tuple7Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple7Sym1 x :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) #

SingI d1 => SingI1 (Tuple6Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple6Sym2 d1 x :: TyFun c (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f)))) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple5Sym3 d1 d2 :: c -> TyFun d3 (e ~> (a, b, c, d3, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple5Sym3 d1 d2 x :: TyFun d3 (e ~> (a, b, c, d3, e)) -> Type) #

SingI d1 => SingI1 (Tuple7Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple7Sym2 d1 x :: TyFun c (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g))))) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple6Sym3 d1 d2 :: c -> TyFun d3 (e ~> (f ~> (a, b, c, d3, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple6Sym3 d1 d2 x :: TyFun d3 (e ~> (f ~> (a, b, c, d3, e, f))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple5Sym4 d1 d2 d3 :: d4 -> TyFun e (a, b, c, d4, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple5Sym4 d1 d2 d3 x :: TyFun e (a, b, c, d4, e) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple7Sym3 d1 d2 :: c -> TyFun d3 (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple7Sym3 d1 d2 x :: TyFun d3 (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g)))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple6Sym4 d1 d2 d3 :: d4 -> TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple6Sym4 d1 d2 d3 x :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple7Sym4 d1 d2 d3 :: d4 -> TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple7Sym4 d1 d2 d3 x :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI1 (Tuple6Sym5 d1 d2 d3 d5 :: e -> TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: e). Sing x -> Sing (Tuple6Sym5 d1 d2 d3 d5 x :: TyFun f (a, b, c, d4, e, f) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI1 (Tuple7Sym5 d1 d2 d3 d5 :: e -> TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: e). Sing x -> Sing (Tuple7Sym5 d1 d2 d3 d5 x :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI1 (Tuple7Sym6 d1 d2 d3 d5 d6 :: f -> TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: f). Sing x -> Sing (Tuple7Sym6 d1 d2 d3 d5 d6 x :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

SingI2 (Zip3Sym2 :: [a] -> [b] -> TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: [a]) (y :: [b]). Sing x -> Sing y -> Sing (Zip3Sym2 x y :: TyFun [c] [(a, b, c)] -> Type) #

SingI d2 => SingI2 (ZipWith3Sym3 d2 :: [a] -> [b] -> TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: [a]) (y :: [b]). Sing x -> Sing y -> Sing (ZipWith3Sym3 d2 x y) #

(SApplicative f, SingI d2) => SingI2 (LiftA3Sym3 d2 :: f a -> f b -> TyFun (f c) (f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: f a) (y :: f b). Sing x -> Sing y -> Sing (LiftA3Sym3 d2 x y) #

(SMonad m, SingI d) => SingI2 (LiftM3Sym3 d :: m a1 -> m a2 -> TyFun (m a3) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a1) (y :: m a2). Sing x -> Sing y -> Sing (LiftM3Sym3 d x y) #

(SMonad m, SingI d) => SingI2 (LiftM4Sym3 d :: m a1 -> m a2 -> TyFun (m a3) (m a4 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a1) (y :: m a2). Sing x -> Sing y -> Sing (LiftM4Sym3 d x y) #

(SMonad m, SingI d) => SingI2 (LiftM5Sym3 d :: m a1 -> m a2 -> TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a1) (y :: m a2). Sing x -> Sing y -> Sing (LiftM5Sym3 d x y) #

(SMonad m, SingI d1, SingI d2) => SingI2 (LiftM4Sym4 d1 d2 :: m a2 -> m a3 -> TyFun (m a4) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a2) (y :: m a3). Sing x -> Sing y -> Sing (LiftM4Sym4 d1 d2 x y) #

(SMonad m, SingI d1, SingI d2) => SingI2 (LiftM5Sym4 d1 d2 :: m a2 -> m a3 -> TyFun (m a4) (m a5 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a2) (y :: m a3). Sing x -> Sing y -> Sing (LiftM5Sym4 d1 d2 x y) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI2 (LiftM5Sym5 d1 d2 d3 :: m a3 -> m a4 -> TyFun (m a5) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: m a3) (y :: m a4). Sing x -> Sing y -> Sing (LiftM5Sym5 d1 d2 d3 x y) #

SingI1 ((!!@#@$$) :: NonEmpty a -> TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: NonEmpty a). Sing x -> Sing ((!!@#@$$) x) #

SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IsPrefixOfSym1 x) #

SingI1 ((!!@#@$$) :: [a] -> TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing ((!!@#@$$) x) #

SingI1 (IntercalateSym1 :: [a] -> TyFun [[a]] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IntercalateSym1 x) #

SEq a => SingI1 (IsInfixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IsInfixOfSym1 x) #

SEq a => SingI1 (IsPrefixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IsPrefixOfSym1 x) #

SEq a => SingI1 (IsSuffixOfSym1 :: [a] -> TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IsSuffixOfSym1 x) #

SEq a => SingI1 (IntersectSym1 :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IntersectSym1 x) #

SEq a => SingI1 (UnionSym1 :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (UnionSym1 x) #

SEq a => SingI1 ((\\@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing ((\\@#@$$) x) #

SingI1 ((++@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing ((++@#@$$) x) #

SShow a => SingI1 (ShowListSym1 :: [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListSym1 x) #

SingI1 (ZipSym1 :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: NonEmpty a). Sing x -> Sing (ZipSym1 x :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) #

SingI d => SingI1 (DeleteFirstsBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (DeleteFirstsBySym2 d x) #

SingI d => SingI1 (IntersectBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (IntersectBySym2 d x) #

SingI d => SingI1 (UnionBySym2 d :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (UnionBySym2 d x) #

SingI1 (ZipSym1 :: [a] -> TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipSym1 x :: TyFun [b] [(a, b)] -> Type) #

SingI d => SingI1 (ShowListWithSym2 d :: [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListWithSym2 d x) #

SAlternative f => SingI1 ((<|>@#@$$) :: f a -> TyFun (f a) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<|>@#@$$) x) #

SMonadPlus m => SingI1 (MplusSym1 :: m a -> TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a). Sing x -> Sing (MplusSym1 x) #

SingI1 (Zip3Sym1 :: [a] -> TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (Zip3Sym1 x :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) #

SApplicative f => SingI1 ((<*>@#@$$) :: f (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f (a ~> b)). Sing x -> Sing ((<*>@#@$$) x) #

SFunctor f => SingI1 ((<&>@#@$$) :: f a -> TyFun (a ~> b) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<&>@#@$$) x :: TyFun (a ~> b) (f b) -> Type) #

SFunctor f => SingI1 (($>@#@$$) :: f a -> TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (($>@#@$$) x :: TyFun b (f b) -> Type) #

SApplicative f => SingI1 ((<**>@#@$$) :: f a -> TyFun (f (a ~> b)) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<**>@#@$$) x :: TyFun (f (a ~> b)) (f b) -> Type) #

SApplicative f => SingI1 ((<*@#@$$) :: f a -> TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<*@#@$$) x :: TyFun (f b) (f a) -> Type) #

SApplicative f => SingI1 ((*>@#@$$) :: f a -> TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((*>@#@$$) x :: TyFun (f b) (f b) -> Type) #

SMonad m => SingI1 (ApSym1 :: m (a ~> b) -> TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m (a ~> b)). Sing x -> Sing (ApSym1 x) #

SMonad m => SingI1 ((>>=@#@$$) :: m a -> TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a). Sing x -> Sing ((>>=@#@$$) x :: TyFun (a ~> m b) (m b) -> Type) #

SMonadZip m => SingI1 (MzipSym1 :: m a -> TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: m a). Sing x -> Sing (MzipSym1 x :: TyFun (m b) (m (a, b)) -> Type) #

SMonad m => SingI1 ((>>@#@$$) :: m a -> TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a). Sing x -> Sing ((>>@#@$$) x :: TyFun (m b) (m b) -> Type) #

SingI d => SingI1 (ZipWithSym2 d :: NonEmpty a -> TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: NonEmpty a). Sing x -> Sing (ZipWithSym2 d x) #

SingI d => SingI1 (ZipWithSym2 d :: [a] -> TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWithSym2 d x) #

SingI d => SingI1 (Zip3Sym2 d :: [b] -> TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [b]). Sing x -> Sing (Zip3Sym2 d x :: TyFun [c] [(a, b, c)] -> Type) #

SingI1 (PairSym1 :: f a -> TyFun (g a) (Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (PairSym1 x :: TyFun (g a) (Product f g a) -> Type) #

(SFoldable t, SApplicative f) => SingI1 (For_Sym1 :: t a -> TyFun (a ~> f b) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: t a). Sing x -> Sing (For_Sym1 x :: TyFun (a ~> f b) (f ()) -> Type) #

(STraversable t, SApplicative f) => SingI1 (ForSym1 :: t a -> TyFun (a ~> f b) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: t a). Sing x -> Sing (ForSym1 x :: TyFun (a ~> f b) (f (t b)) -> Type) #

(SFoldable t, SMonad m) => SingI1 (ForM_Sym1 :: t a -> TyFun (a ~> m b) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: t a). Sing x -> Sing (ForM_Sym1 x :: TyFun (a ~> m b) (m ()) -> Type) #

(STraversable t, SMonad m) => SingI1 (ForMSym1 :: t a -> TyFun (a ~> m b) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: t a). Sing x -> Sing (ForMSym1 x :: TyFun (a ~> m b) (m (t b)) -> Type) #

SingI d2 => SingI1 (ZipWith3Sym2 d2 :: [a] -> TyFun [b] ([c] ~> [d1]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWith3Sym2 d2 x) #

(SApplicative m, SingI d) => SingI1 (ZipWithM_Sym2 d :: [a] -> TyFun [b] (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWithM_Sym2 d x) #

(SApplicative m, SingI d) => SingI1 (ZipWithMSym2 d :: [a] -> TyFun [b] (m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWithMSym2 d x) #

(SApplicative f, SingI d) => SingI1 (LiftA2Sym2 d :: f a -> TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (LiftA2Sym2 d x) #

(SMonadZip m, SingI d) => SingI1 (MzipWithSym2 d :: m a -> TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: m a). Sing x -> Sing (MzipWithSym2 d x) #

(SMonad m, SingI d) => SingI1 (LiftM2Sym2 d :: m a1 -> TyFun (m a2) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a1). Sing x -> Sing (LiftM2Sym2 d x) #

(SingI d2, SingI d3) => SingI1 (ZipWith3Sym3 d2 d3 :: [b] -> TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [b]). Sing x -> Sing (ZipWith3Sym3 d2 d3 x) #

(SApplicative f, SingI d2) => SingI1 (LiftA3Sym2 d2 :: f a -> TyFun (f b) (f c ~> f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (LiftA3Sym2 d2 x) #

(SMonad m, SingI d) => SingI1 (LiftM3Sym2 d :: m a1 -> TyFun (m a2) (m a3 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a1). Sing x -> Sing (LiftM3Sym2 d x) #

(SApplicative f, SingI d2, SingI d3) => SingI1 (LiftA3Sym3 d2 d3 :: f b -> TyFun (f c) (f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f b). Sing x -> Sing (LiftA3Sym3 d2 d3 x) #

(SMonad m, SingI d) => SingI1 (LiftM4Sym2 d :: m a1 -> TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a1). Sing x -> Sing (LiftM4Sym2 d x) #

(SMonad m, SingI d1, SingI d2) => SingI1 (LiftM3Sym3 d1 d2 :: m a2 -> TyFun (m a3) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a2). Sing x -> Sing (LiftM3Sym3 d1 d2 x) #

(SMonad m, SingI d) => SingI1 (LiftM5Sym2 d :: m a1 -> TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a1). Sing x -> Sing (LiftM5Sym2 d x) #

(SMonad m, SingI d1, SingI d2) => SingI1 (LiftM4Sym3 d1 d2 :: m a2 -> TyFun (m a3) (m a4 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a2). Sing x -> Sing (LiftM4Sym3 d1 d2 x) #

(SMonad m, SingI d1, SingI d2) => SingI1 (LiftM5Sym3 d1 d2 :: m a2 -> TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a2). Sing x -> Sing (LiftM5Sym3 d1 d2 x) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI1 (LiftM4Sym4 d1 d2 d3 :: m a3 -> TyFun (m a4) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a3). Sing x -> Sing (LiftM4Sym4 d1 d2 d3 x) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI1 (LiftM5Sym4 d1 d2 d3 :: m a3 -> TyFun (m a4) (m a5 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a3). Sing x -> Sing (LiftM5Sym4 d1 d2 d3 x) #

(SMonad m, SingI d1, SingI d2, SingI d3, SingI d4) => SingI1 (LiftM5Sym5 d1 d2 d3 d4 :: m a4 -> TyFun (m a5) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a4). Sing x -> Sing (LiftM5Sym5 d1 d2 d3 d4 x) #

(SingKind k1, SingKind k2) => SingKind (k1 ~> k2) # 
Instance details

Defined in Data.Singletons

Associated Types

type Demote (k1 ~> k2) 
Instance details

Defined in Data.Singletons

type Demote (k1 ~> k2) = Demote k1 -> Demote k2

Methods

fromSing :: forall (a :: k1 ~> k2). Sing a -> Demote (k1 ~> k2) #

toSing :: Demote (k1 ~> k2) -> SomeSing (k1 ~> k2) #

PMonoid (a ~> b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
SMonoid b => SMonoid (a ~> b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: a ~> b) Source #

sMappend :: forall (t1 :: a ~> b) (t2 :: a ~> b). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [a ~> b]). Sing t -> Sing (Mconcat t) Source #

PSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

SSemigroup b => SSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: a ~> b) (t2 :: a ~> b). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (a ~> b)). Sing t -> Sing (Sconcat t) Source #

SingI XorSym0 Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing XorSym0 #

SingI GetAllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing GetAllSym0 #

SingI GetAnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing GetAnySym0 #

SingI AllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing AllSym0 #

SingI AnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing AnySym0 #

SingI ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI UnlinesSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI UnwordsSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowCommaSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI DivSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing DivSym0 #

SingI ModSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing ModSym0 #

SingI (^@#@$) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing (^@#@$) #

SingI Log2Sym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing Log2Sym0 #

SingI NatToCharSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingI (&&@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (&&@#@$) #

SingI (||@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (||@#@$) #

SingI NotSym0 Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing NotSym0 #

SingI ConsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingI CharToNatSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingI UnconsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings XorSym0 Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings GetAllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings GetAnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings KnownNatSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings DivSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings ModSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings QuotSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings RemSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (^@#@$) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings DivModSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings QuotRemSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings Log2Sym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings NatToCharSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings AllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings AnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (&&@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (||@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings NotSym0 Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings ConsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings CharToNatSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings KnownCharSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings UnlinesSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings UnwordsSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings UnconsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings KnownSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings ShowCommaSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI2 (InsertBySym2 :: (a ~> (a ~> Ordering)) -> a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Ordering)) (y :: a). Sing x -> Sing y -> Sing (InsertBySym2 x y) #

SingI2 (DeleteBySym2 :: (a ~> (a ~> Bool)) -> a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Bool)) (y :: a). Sing x -> Sing y -> Sing (DeleteBySym2 x y) #

SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanrSym2 x y) #

SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanrSym2 x y) #

SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanlSym2 x y) #

SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanlSym2 x y) #

SOrd a => SingI2 (ComparingSym2 :: (b ~> a) -> b -> TyFun b Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing2 :: forall (x :: b ~> a) (y :: b). Sing x -> Sing y -> Sing (ComparingSym2 x y) #

SingI2 (CurrySym2 :: ((a, b) ~> c) -> a -> TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing2 :: forall (x :: (a, b) ~> c) (y :: a). Sing x -> Sing y -> Sing (CurrySym2 x y) #

SFoldable t => SingI2 (Foldr'Sym2 :: (a ~> (b ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (Foldr'Sym2 x y :: TyFun (t a) b -> Type) #

SFoldable t => SingI2 (FoldrSym2 :: (a ~> (b ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (FoldrSym2 x y :: TyFun (t a) b -> Type) #

SingI2 (FlipSym2 :: (a ~> (b ~> c)) -> b -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: b). Sing x -> Sing y -> Sing (FlipSym2 x y) #

SFoldable t => SingI2 (Foldl'Sym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (Foldl'Sym2 x y :: TyFun (t a) b -> Type) #

SFoldable t => SingI2 (FoldlSym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (FoldlSym2 x y :: TyFun (t a) b -> Type) #

STraversable t => SingI2 (MapAccumLSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> (a, c))) (y :: a). Sing x -> Sing y -> Sing (MapAccumLSym2 x y :: TyFun (t b) (a, t c) -> Type) #

STraversable t => SingI2 (MapAccumRSym2 :: (a ~> (b ~> (a, c))) -> a -> TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> (a, c))) (y :: a). Sing x -> Sing y -> Sing (MapAccumRSym2 x y :: TyFun (t b) (a, t c) -> Type) #

(SFoldable t, SMonad m) => SingI2 (FoldrMSym2 :: (a ~> (b ~> m b)) -> b -> TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> m b)) (y :: b). Sing x -> Sing y -> Sing (FoldrMSym2 x y :: TyFun (t a) (m b) -> Type) #

SingI d => SingI2 (OnSym3 d :: (a ~> b) -> a -> TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing2 :: forall (x :: a ~> b) (y :: a). Sing x -> Sing y -> Sing (OnSym3 d x y) #

(SFoldable t, SMonad m) => SingI2 (FoldlMSym2 :: (b ~> (a ~> m b)) -> b -> TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> m b)) (y :: b). Sing x -> Sing y -> Sing (FoldlMSym2 x y :: TyFun (t a) (m b) -> Type) #

SingI (GetFirstSym0 :: TyFun (First a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetFirstSym0 :: TyFun (First a) a -> Type) #

SingI (GetLastSym0 :: TyFun (Last a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetLastSym0 :: TyFun (Last a) a -> Type) #

SingI (GetMaxSym0 :: TyFun (Max a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetMaxSym0 :: TyFun (Max a) a -> Type) #

SingI (GetMinSym0 :: TyFun (Min a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetMinSym0 :: TyFun (Min a) a -> Type) #

SingI (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SingI (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SEq a => SingI (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) #

SEq a => SingI (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) #

SingI (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) #

SOrd a => SingI (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) #

SingI ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) #

SingI (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) #

SingI (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) #

SingI (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) #

SingI (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) #

SingI (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) #

SingI (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (HeadSym0 :: TyFun (NonEmpty a) a -> Type) #

SingI (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (LastSym0 :: TyFun (NonEmpty a) a -> Type) #

SSemigroup a => SingI (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) #

SingI (AbsurdSym0 :: TyFun Void a -> Type) Source # 
Instance details

Defined in Data.Void.Singletons

Methods

sing :: Sing (AbsurdSym0 :: TyFun Void a -> Type) #

SingI (RunIdentitySym0 :: TyFun (Identity a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (RunIdentitySym0 :: TyFun (Identity a) a -> Type) #

SingI (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) #

SingI (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) #

SingI (GetDownSym0 :: TyFun (Down a) a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (GetDownSym0 :: TyFun (Down a) a -> Type) #

SingI (GetDualSym0 :: TyFun (Dual a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetDualSym0 :: TyFun (Dual a) a -> Type) #

SingI (GetProductSym0 :: TyFun (Product a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetProductSym0 :: TyFun (Product a) a -> Type) #

SingI (GetSumSym0 :: TyFun (Sum a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetSumSym0 :: TyFun (Sum a) a -> Type) #

SingI d => SingI (ShowParenSym1 d :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym1 d) #

SingI (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) #

SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) #

SingI (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) #

SingI (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) #

SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) #

SingI (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) #

SingI (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) #

SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) #

SingI (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) #

SingI (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) #

SingI (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) #

SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) #

SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) #

SingI (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) #

SingI (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) #

SingI (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) #

SingI (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) #

SingI (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) #

SingI (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) #

SingI (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) #

SingI (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) #

SingI (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) #

SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) #

SingI (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) #

SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) #

SingI (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) #

SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SingI ((:$$:@#@$) :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol ~> ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI ((:<>:@#@$) :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol ~> ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) #

SingI (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) #

SingI (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) #

SingI (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) #

SingI (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) #

SingI (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) #

SShow a => SingI (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SingI (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) #

SEnum a => SingI (ToEnumSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (ToEnumSym0 :: TyFun Natural a -> Type) #

SNum a => SingI (FromIntegerSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SingI (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) #

SingI (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) #

SingI (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) #

SingI (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) #

SingI (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) #

SingI (FromJustSym0 :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromJustSym0 :: TyFun (Maybe a) a -> Type) #

SApplicative f => SingI (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) #

SApplicative f => SingI (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) #

SAlternative f => SingI (GuardSym0 :: TyFun Bool (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (GuardSym0 :: TyFun Bool (f ()) -> Type) #

SingI (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) #

SingI (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) #

SingI (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) #

SingI (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) #

SingI (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) #

SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) #

SingI ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) #

SingI (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) #

SEq a => SingI (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) #

SEq a => SingI (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) #

SEq a => SingI (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) #

SEq a => SingI (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) #

SEq a => SingI (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) #

SEq a => SingI ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) #

SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) #

SShow a => SingI (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) #

SingI (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) #

SingI (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) #

SEq a => SingI (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) #

SEq a => SingI (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (GroupSym0 :: TyFun [a] [[a]] -> Type) #

SingI (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InitsSym0 :: TyFun [a] [[a]] -> Type) #

SingI (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (PermutationsSym0 :: TyFun [a] [[a]] -> Type) #

SingI (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) #

SingI (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TailsSym0 :: TyFun [a] [[a]] -> Type) #

SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InitSym0 :: TyFun [a] [a] -> Type) #

SEq a => SingI (NubSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (NubSym0 :: TyFun [a] [a] -> Type) #

SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReverseSym0 :: TyFun [a] [a] -> Type) #

SOrd a => SingI (SortSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SortSym0 :: TyFun [a] [a] -> Type) #

SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TailSym0 :: TyFun [a] [a] -> Type) #

SingI (HeadSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (HeadSym0 :: TyFun [a] a -> Type) #

SingI (LastSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LastSym0 :: TyFun [a] a -> Type) #

SMonoid a => SingI (MconcatSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MconcatSym0 :: TyFun [a] a -> Type) #

SingI (TextSym0 :: TyFun Symbol (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI d => SingI (ShowCharSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowCharSym1 d) #

SingI d => SingI (ShowStringSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowStringSym1 d) #

SIsString a => SingI (FromStringSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in Data.String.Singletons

Methods

sing :: Sing (FromStringSym0 :: TyFun Symbol a -> Type) #

SingI (ErrorSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing (ErrorSym0 :: TyFun Symbol a -> Type) #

SingI (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SingI (FirstSym0 :: TyFun a (First a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (FirstSym0 :: TyFun a (First a) -> Type) #

SingI (LastSym0 :: TyFun a (Last a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (LastSym0 :: TyFun a (Last a) -> Type) #

SingI (MaxSym0 :: TyFun a (Max a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (MaxSym0 :: TyFun a (Max a) -> Type) #

SingI (MinSym0 :: TyFun a (Min a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (MinSym0 :: TyFun a (Min a) -> Type) #

SingI (IdentitySym0 :: TyFun a (Identity a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (IdentitySym0 :: TyFun a (Identity a) -> Type) #

SingI (DownSym0 :: TyFun a (Down a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (DownSym0 :: TyFun a (Down a) -> Type) #

SingI (DualSym0 :: TyFun a (Dual a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (DualSym0 :: TyFun a (Dual a) -> Type) #

SingI (ProductSym0 :: TyFun a (Product a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (ProductSym0 :: TyFun a (Product a) -> Type) #

SingI (SumSym0 :: TyFun a (Sum a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (SumSym0 :: TyFun a (Sum a) -> Type) #

SingI ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) #

SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) #

SingI ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) #

SEq a => SingI (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) #

SEq a => SingI (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) #

SEq a => SingI (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) #

SOrd a => SingI (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) #

SingI (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) #

SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) #

SShow a => SingI (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) #

SOrd a => SingI (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) #

SingI (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) #

SEnum a => SingI (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) #

SEq a => SingI ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SEq a => SingI ((==@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((==@#@$) :: TyFun a (a ~> Bool) -> Type) #

SOrd a => SingI ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SOrd a => SingI ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<@#@$) :: TyFun a (a ~> Bool) -> Type) #

SOrd a => SingI ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SOrd a => SingI ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>@#@$) :: TyFun a (a ~> Bool) -> Type) #

SEnum a => SingI (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) #

SMonoid a => SingI (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MappendSym0 :: TyFun a (a ~> a) -> Type) #

SOrd a => SingI (MaxSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MaxSym0 :: TyFun a (a ~> a) -> Type) #

SOrd a => SingI (MinSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MinSym0 :: TyFun a (a ~> a) -> Type) #

SSemigroup a => SingI ((<>@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing ((<>@#@$) :: TyFun a (a ~> a) -> Type) #

SingI (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) #

SNum a => SingI ((*@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((*@#@$) :: TyFun a (a ~> a) -> Type) #

SNum a => SingI ((+@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((+@#@$) :: TyFun a (a ~> a) -> Type) #

SNum a => SingI ((-@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((-@#@$) :: TyFun a (a ~> a) -> Type) #

SNum a => SingI (SubtractSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SubtractSym0 :: TyFun a (a ~> a) -> Type) #

SEnum a => SingI (FromEnumSym0 :: TyFun a Natural -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (FromEnumSym0 :: TyFun a Natural -> Type) #

SingI (JustSym0 :: TyFun a (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (JustSym0 :: TyFun a (Maybe a) -> Type) #

SShow a => SingI (Show_Sym0 :: TyFun a Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (Show_Sym0 :: TyFun a Symbol -> Type) #

SEnum a => SingI (PredSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (PredSym0 :: TyFun a a -> Type) #

SEnum a => SingI (SuccSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (SuccSym0 :: TyFun a a -> Type) #

SingI (IdSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (IdSym0 :: TyFun a a -> Type) #

SNum a => SingI (AbsSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (AbsSym0 :: TyFun a a -> Type) #

SNum a => SingI (NegateSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (NegateSym0 :: TyFun a a -> Type) #

SNum a => SingI (SignumSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SignumSym0 :: TyFun a a -> Type) #

SingI (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) #

SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AndSym0 :: TyFun (t Bool) Bool -> Type) #

SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (OrSym0 :: TyFun (t Bool) Bool -> Type) #

SingI (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI ((<=?@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SingI x => SingI (DivSym1 x :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing (DivSym1 x) #

SingI x => SingI (ModSym1 x :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing (ModSym1 x) #

SingI x => SingI ((^@#@$$) x :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing ((^@#@$$) x) #

SingI (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) #

SingI x => SingI ((&&@#@$$) x :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing ((&&@#@$$) x) #

SingI x => SingI ((||@#@$$) x :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing ((||@#@$$) x) #

SingI x => SingI (ConsSymbolSym1 x :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing (ConsSymbolSym1 x) #

SuppressUnusedWarnings (GetFirstSym0 :: TyFun (First a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (GetLastSym0 :: TyFun (Last a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (GetMaxSym0 :: TyFun (Max a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (GetMinSym0 :: TyFun (Min a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Group1Sym0 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (NubSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ReverseSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SortSym0 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (UnconsSym0 :: TyFun (NonEmpty a) (a, Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (InitSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TailSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (HeadSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (LastSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

SuppressUnusedWarnings (AbsurdSym0 :: TyFun Void a -> Type) Source # 
Instance details

Defined in Data.Void.Singletons

SuppressUnusedWarnings (RunIdentitySym0 :: TyFun (Identity a) a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (GetDownSym0 :: TyFun (Down a) a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (GetDualSym0 :: TyFun (Dual a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (GetProductSym0 :: TyFun (Product a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (GetSumSym0 :: TyFun (Sum a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ((:$$:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings ((:<>:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DivSym1 a6989586621679378709 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (ModSym1 a6989586621679379154 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (QuotSym1 a6989586621679379824 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (RemSym1 a6989586621679379813 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings ((^@#@$$) a6989586621679369666 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (DivModSym1 a6989586621679379842 :: TyFun Natural (Natural, Natural) -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (QuotRemSym1 a6989586621679379835 :: TyFun Natural (Natural, Natural) -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (ToEnumSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (FromIntegerSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (IsNothingSym0 :: TyFun (Maybe a) Bool -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (MaybeToListSym0 :: TyFun (Maybe a) [a] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (FromJustSym0 :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings ((&&@#@$$) a6989586621679123502 :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings ((||@#@$$) a6989586621679123865 :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (GuardSym0 :: TyFun Bool (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (CatMaybesSym0 :: TyFun [Maybe a] [a] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (TransposeSym0 :: TyFun [[a]] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InitsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TailsSym0 :: TyFun [a] (NonEmpty [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (FromListSym0 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (NonEmpty_Sym0 :: TyFun [a] (Maybe (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ListToMaybeSym0 :: TyFun [a] (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (GroupSym0 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InitsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (PermutationsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SubsequencesSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TailsSym0 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InitSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (NubSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ReverseSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SortSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TailSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (HeadSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (LastSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (MconcatSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (ConsSymbolSym1 a6989586621679381116 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (FromStringSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in Data.String.Singletons

SuppressUnusedWarnings (ErrorSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (FirstSym0 :: TyFun a (First a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (LastSym0 :: TyFun a (Last a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (MaxSym0 :: TyFun a (Max a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (MinSym0 :: TyFun a (Min a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (IdentitySym0 :: TyFun a (Identity a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (DownSym0 :: TyFun a (Down a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (DualSym0 :: TyFun a (Dual a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (ProductSym0 :: TyFun a (Product a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (SumSym0 :: TyFun a (Sum a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((==@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (MaxSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (MinSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((<>@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

SuppressUnusedWarnings (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings ((*@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings ((+@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings ((-@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (SubtractSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (FromEnumSym0 :: TyFun a Natural -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (JustSym0 :: TyFun a (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Show_Sym0 :: TyFun a Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (PredSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (SuccSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (IdSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (AbsSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (NegateSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (SignumSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((<=?@#@$) :: TyFun k (k ~> Bool) -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (TextSym0 :: TyFun s (ErrorMessage' s) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SingI2 (ShowListWithSym2 :: (a ~> (Symbol ~> Symbol)) -> [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: a ~> (Symbol ~> Symbol)) (y :: [a]). Sing x -> Sing y -> Sing (ShowListWithSym2 x y) #

SingI2 (DeleteFirstsBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Bool)) (y :: [a]). Sing x -> Sing y -> Sing (DeleteFirstsBySym2 x y) #

SingI2 (IntersectBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Bool)) (y :: [a]). Sing x -> Sing y -> Sing (IntersectBySym2 x y) #

SingI2 (UnionBySym2 :: (a ~> (a ~> Bool)) -> [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (a ~> Bool)) (y :: [a]). Sing x -> Sing y -> Sing (UnionBySym2 x y) #

SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> NonEmpty a -> TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: NonEmpty a). Sing x -> Sing y -> Sing (ZipWithSym2 x y) #

SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> [a] -> TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: [a]). Sing x -> Sing y -> Sing (ZipWithSym2 x y) #

SingI2 (ZipWith3Sym2 :: (a ~> (b ~> (c ~> d))) -> [a] -> TyFun [b] ([c] ~> [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> (c ~> d))) (y :: [a]). Sing x -> Sing y -> Sing (ZipWith3Sym2 x y) #

SApplicative f => SingI2 (LiftA2Sym2 :: (a ~> (b ~> c)) -> f a -> TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: f a). Sing x -> Sing y -> Sing (LiftA2Sym2 x y) #

SMonadZip m => SingI2 (MzipWithSym2 :: (a ~> (b ~> c)) -> m a -> TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: m a). Sing x -> Sing y -> Sing (MzipWithSym2 x y) #

SApplicative m => SingI2 (ZipWithM_Sym2 :: (a ~> (b ~> m c)) -> [a] -> TyFun [b] (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> m c)) (y :: [a]). Sing x -> Sing y -> Sing (ZipWithM_Sym2 x y) #

SApplicative m => SingI2 (ZipWithMSym2 :: (a ~> (b ~> m c)) -> [a] -> TyFun [b] (m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> m c)) (y :: [a]). Sing x -> Sing y -> Sing (ZipWithMSym2 x y) #

SMonad m => SingI2 (LiftM2Sym2 :: (a1 ~> (a2 ~> r)) -> m a1 -> TyFun (m a2) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a1 ~> (a2 ~> r)) (y :: m a1). Sing x -> Sing y -> Sing (LiftM2Sym2 x y) #

SApplicative f => SingI2 (LiftA3Sym2 :: (a ~> (b ~> (c ~> d))) -> f a -> TyFun (f b) (f c ~> f d) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> (c ~> d))) (y :: f a). Sing x -> Sing y -> Sing (LiftA3Sym2 x y) #

SMonad m => SingI2 (LiftM3Sym2 :: (a1 ~> (a2 ~> (a3 ~> r))) -> m a1 -> TyFun (m a2) (m a3 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a1 ~> (a2 ~> (a3 ~> r))) (y :: m a1). Sing x -> Sing y -> Sing (LiftM3Sym2 x y) #

SMonad m => SingI2 (LiftM4Sym2 :: (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) -> m a1 -> TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (y :: m a1). Sing x -> Sing y -> Sing (LiftM4Sym2 x y) #

SMonad m => SingI2 (LiftM5Sym2 :: (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) -> m a1 -> TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (y :: m a1). Sing x -> Sing y -> Sing (LiftM5Sym2 x y) #

SingI (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) #

SingI d => SingI (GroupBy1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBy1Sym1 d) #

SingI d => SingI ((<|@#@$$) d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((<|@#@$$) d) #

SingI d => SingI (ConsSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ConsSym1 d) #

SingI d => SingI (IntersperseSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IntersperseSym1 d) #

SingI d => SingI (NubBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (NubBySym1 d) #

SingI d => SingI (Scanl1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanl1Sym1 d) #

SingI d => SingI (Scanr1Sym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (Scanr1Sym1 d) #

SingI d => SingI (SortBySym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortBySym1 d) #

SingI (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) #

SingI d => SingI (BreakSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (BreakSym1 d) #

SingI d => SingI (PartitionSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (PartitionSym1 d) #

SingI d => SingI (SpanSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SpanSym1 d) #

SingI d => SingI (SplitAtSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SplitAtSym1 d :: TyFun (NonEmpty a) ([a], [a]) -> Type) #

(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (IsPrefixOfSym1 d) #

SingI d => SingI (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropSym1 d :: TyFun (NonEmpty a) [a] -> Type) #

SingI d => SingI (DropWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (DropWhileSym1 d) #

SingI d => SingI (FilterSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (FilterSym1 d) #

SingI d => SingI (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeSym1 d :: TyFun (NonEmpty a) [a] -> Type) #

SingI d => SingI (TakeWhileSym1 d :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (TakeWhileSym1 d) #

SingI (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) #

SingI (IsRightSym0 :: TyFun (Either a b) Bool -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (IsRightSym0 :: TyFun (Either a b) Bool -> Type) #

SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) #

SFoldable t => SingI (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) #

SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) #

SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) #

SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) #

SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) #

SingI (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) #

SingI (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) #

SingI (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) #

SMonadPlus m => SingI (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) #

SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) #

SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) #

SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) #

SingI d => SingI (UntilSym1 d :: TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym1 d) #

SOrd b => SingI (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) #

SEq b => SingI (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) #

SingI (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) #

SOrd b => SingI (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) #

SEq b => SingI (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) #

SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) #

SingI (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) #

SingI (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) #

SApplicative m => SingI (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) #

SOrd o => SingI (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) #

SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) #

SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) #

SingI (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) #

SOrd a => SingI (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) #

SingI x => SingI ((:$$:@#@$$) x :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ((:$$:@#@$$) x) #

SingI x => SingI ((:<>:@#@$$) x :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ((:<>:@#@$$) x) #

SApplicative m => SingI (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) #

SApplicative m => SingI (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) #

SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing ((!!@#@$$) d) #

SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((!!@#@$$) d) #

SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromMaybeSym1 d) #

SingI (SwapSym0 :: TyFun (a, b) (b, a) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (SwapSym0 :: TyFun (a, b) (b, a) -> Type) #

SingI (FstSym0 :: TyFun (a, b) a -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (FstSym0 :: TyFun (a, b) a -> Type) #

SingI (SndSym0 :: TyFun (a, b) b -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (SndSym0 :: TyFun (a, b) b -> Type) #

SingI (LeftsSym0 :: TyFun [Either a b] [a] -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (LeftsSym0 :: TyFun [Either a b] [a] -> Type) #

SingI (RightsSym0 :: TyFun [Either a b] [b] -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (RightsSym0 :: TyFun [Either a b] [b] -> Type) #

SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) #

SMonadFail m => SingI (FailSym0 :: TyFun [Char] (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sing :: Sing (FailSym0 :: TyFun [Char] (m a) -> Type) #

SingI d => SingI (IntercalateSym1 d :: TyFun [[a]] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntercalateSym1 d) #

(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (InsertSym1 d) #

SingI d => SingI ((:|@#@$$) d :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:|@#@$$) d) #

SingI d => SingI (DeleteFirstsBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI d => SingI (IntersectBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectBySym1 d) #

SingI d => SingI (UnionBySym1 d :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionBySym1 d) #

SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) #

SingI d => SingI (ShowListWithSym1 d :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym1 d) #

(SEq a, SingI d) => SingI (ElemIndexSym1 d :: TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndexSym1 d) #

SingI d => SingI (FindIndexSym1 d :: TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndexSym1 d) #

SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (BreakSym1 d) #

SingI d => SingI (PartitionSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (PartitionSym1 d) #

SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SpanSym1 d) #

SingI d => SingI (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) #

(SEq a, SingI d) => SingI (IsInfixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsInfixOfSym1 d) #

(SEq a, SingI d) => SingI (IsPrefixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsPrefixOfSym1 d) #

(SEq a, SingI d) => SingI (IsSuffixOfSym1 d :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IsSuffixOfSym1 d) #

SingI d => SingI (GroupBySym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupBySym1 d) #

(SEq a, SingI d) => SingI (ElemIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ElemIndicesSym1 d) #

SingI d => SingI (FindIndicesSym1 d :: TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FindIndicesSym1 d) #

SingI d => SingI (GroupBySym1 d :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (GroupBySym1 d) #

(SEq a, SingI d) => SingI (DeleteSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteSym1 d) #

SingI d => SingI (DropSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropSym1 d :: TyFun [a] [a] -> Type) #

SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileEndSym1 d) #

SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileSym1 d) #

SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FilterSym1 d) #

(SOrd a, SingI d) => SingI (InsertSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertSym1 d) #

(SEq a, SingI d) => SingI (IntersectSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectSym1 d) #

SingI d => SingI (IntersperseSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersperseSym1 d) #

SingI d => SingI (NubBySym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (NubBySym1 d) #

SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanl1Sym1 d) #

SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanr1Sym1 d) #

SingI d => SingI (SortBySym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SortBySym1 d) #

SingI d => SingI (TakeSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeSym1 d :: TyFun [a] [a] -> Type) #

SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeWhileSym1 d) #

(SEq a, SingI d) => SingI (UnionSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionSym1 d) #

(SEq a, SingI d) => SingI ((\\@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((\\@#@$$) d) #

SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:@#@$$) d) #

SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((++@#@$$) d) #

SingI d => SingI (Foldl1'Sym1 d :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Foldl1'Sym1 d) #

SNum i => SingI (GenericLengthSym0 :: TyFun [a] i -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (GenericLengthSym0 :: TyFun [a] i -> Type) #

(SShow a, SingI d) => SingI (ShowListSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym1 d) #

(SingI d1, SingI d2) => SingI (ShowParenSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym2 d1 d2) #

(SShow a, SingI d) => SingI (ShowsSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym1 d) #

SingI (LeftSym0 :: TyFun a (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (LeftSym0 :: TyFun a (Either a b) -> Type) #

(SOrd a, SingI d) => SingI (CompareSym1 d :: TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (CompareSym1 d) #

SingI ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) #

SingI d => SingI (Bool_Sym1 d :: TyFun a (Bool ~> a) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (Bool_Sym1 d) #

SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) #

SingI d => SingI (DeleteBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteBySym1 d) #

SingI d => SingI (InsertBySym1 d :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertBySym1 d) #

(SShow a, SingI d) => SingI (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) #

(SEnum a, SingI d) => SingI (EnumFromThenToSym1 d :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SingI (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sing :: Sing (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) #

SingI (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) #

SingI (ConstSym0 :: TyFun a (b ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (ConstSym0 :: TyFun a (b ~> a) -> Type) #

SingI (SeqSym0 :: TyFun a (b ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (SeqSym0 :: TyFun a (b ~> b) -> Type) #

SingI (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sing :: Sing (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) #

(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) #

(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) #

(SEq a, SingI d) => SingI ((/=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((/=@#@$$) d) #

(SEq a, SingI d) => SingI ((==@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((==@#@$$) d) #

(SOrd a, SingI d) => SingI ((<=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<=@#@$$) d) #

(SOrd a, SingI d) => SingI ((<@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<@#@$$) d) #

(SOrd a, SingI d) => SingI ((>=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>=@#@$$) d) #

(SOrd a, SingI d) => SingI ((>@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>@#@$$) d) #

SingI d => SingI (ReplicateSym1 d :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReplicateSym1 d :: TyFun a [a] -> Type) #

(SEnum a, SingI d) => SingI (EnumFromToSym1 d :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromToSym1 d) #

(SMonoid a, SingI d) => SingI (MappendSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MappendSym1 d) #

(SOrd a, SingI d) => SingI (MaxSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MaxSym1 d) #

(SOrd a, SingI d) => SingI (MinSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MinSym1 d) #

(SSemigroup a, SingI d) => SingI ((<>@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing ((<>@#@$$) d) #

SingI d => SingI (AsTypeOfSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (AsTypeOfSym1 d) #

(SNum a, SingI d) => SingI ((*@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((*@#@$$) d) #

(SNum a, SingI d) => SingI ((+@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((+@#@$$) d) #

(SNum a, SingI d) => SingI ((-@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((-@#@$$) d) #

(SNum a, SingI d) => SingI (SubtractSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SubtractSym1 d) #

SApplicative f => SingI (PureSym0 :: TyFun a (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (PureSym0 :: TyFun a (f a) -> Type) #

SMonad m => SingI (ReturnSym0 :: TyFun a (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (ReturnSym0 :: TyFun a (m a) -> Type) #

SingI (RightSym0 :: TyFun b (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (RightSym0 :: TyFun b (Either a b) -> Type) #

SingI (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) #

(SApplicative f, SingI d) => SingI (UnlessSym1 d :: TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (UnlessSym1 d :: TyFun (f ()) (f ()) -> Type) #

(SApplicative f, SingI d) => SingI (WhenSym1 d :: TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (WhenSym1 d :: TyFun (f ()) (f ()) -> Type) #

SAlternative f => SingI ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) #

SAlternative f => SingI (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) Source # 
Instance details

Defined in Control.Applicative.Singletons

Methods

sing :: Sing (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) #

SFunctor f => SingI (VoidSym0 :: TyFun (f a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (VoidSym0 :: TyFun (f a) (f ()) -> Type) #

SMonadPlus m => SingI (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) #

SMonad m => SingI (JoinSym0 :: TyFun (m (m a)) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (JoinSym0 :: TyFun (m (m a)) (m a) -> Type) #

SingI (ShowTypeSym0 :: TyFun t (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatSym0 :: TyFun (t [a]) [a] -> Type) #

SFoldable t => SingI (LengthSym0 :: TyFun (t a) Natural -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (LengthSym0 :: TyFun (t a) Natural -> Type) #

SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NullSym0 :: TyFun (t a) Bool -> Type) #

SFoldable t => SingI (ToListSym0 :: TyFun (t a) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ToListSym0 :: TyFun (t a) [a] -> Type) #

(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MaximumSym0 :: TyFun (t a) a -> Type) #

(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MinimumSym0 :: TyFun (t a) a -> Type) #

(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ProductSym0 :: TyFun (t a) a -> Type) #

(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (SumSym0 :: TyFun (t a) a -> Type) #

(SFoldable t, SMonoid m) => SingI (FoldSym0 :: TyFun (t m) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldSym0 :: TyFun (t m) m -> Type) #

SingI x => SingI ((<=?@#@$$) x :: TyFun Natural Bool -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing ((<=?@#@$$) x) #

SingI c => SingI (IfSym1 c :: TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym1 c :: TyFun k (k ~> k) -> Type) #

SuppressUnusedWarnings (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupBy1Sym1 a6989586621680286992 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((<|@#@$$) a6989586621680287295 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ConsSym1 a6989586621680287288 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IntersperseSym1 a6989586621680287177 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (NubBySym1 a6989586621680286869 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Scanl1Sym1 a6989586621680287198 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Scanr1Sym1 a6989586621680287190 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SortBySym1 a6989586621680286856 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (BreakSym1 a6989586621680287110 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (PartitionSym1 a6989586621680287092 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SpanSym1 a6989586621680287119 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SplitAtSym1 a6989586621680287146 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621680286965 :: TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DropSym1 a6989586621680287155 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DropWhileSym1 a6989586621680287128 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (FilterSym1 a6989586621680287101 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TakeSym1 a6989586621680287164 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TakeWhileSym1 a6989586621680287137 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

SuppressUnusedWarnings (IsRightSym0 :: TyFun (Either a b) Bool -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (UntilSym1 a6989586621679154281 :: TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((:$$:@#@$$) a6989586621679803713 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings ((:<>:@#@$$) a6989586621679803710 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings ((!!@#@$$) a6989586621680286938 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((!!@#@$$) a6989586621679544266 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FromMaybeSym1 a6989586621679390214 :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (SwapSym0 :: TyFun (a, b) (b, a) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (FstSym0 :: TyFun (a, b) a -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (SndSym0 :: TyFun (a, b) b -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (LeftsSym0 :: TyFun [Either a b] [a] -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

SuppressUnusedWarnings (RightsSym0 :: TyFun [Either a b] [b] -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FailSym0 :: TyFun [Char] (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

SuppressUnusedWarnings (IntercalateSym1 a6989586621679545415 :: TyFun [[a]] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertSym1 a6989586621680287232 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((:|@#@$$) a6989586621679050362 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679544763 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersectBySym1 a6989586621679544588 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnionBySym1 a6989586621679544211 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ShowListWithSym1 a6989586621679807383 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ElemIndexSym1 a6989586621679544658 :: TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FindIndexSym1 a6989586621679544640 :: TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (StripPrefixSym1 a6989586621679656297 :: TyFun [a] (Maybe [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (BreakSym1 a6989586621679544458 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (PartitionSym1 a6989586621679544342 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SpanSym1 a6989586621679544497 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679545011 :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679545025 :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679545018 :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GroupBySym1 a6989586621680287048 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679544649 :: TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FindIndicesSym1 a6989586621679544619 :: TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GroupBySym1 a6989586621679544364 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DeleteSym1 a6989586621679544803 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679544538 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropWhileSym1 a6989586621679544559 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FilterSym1 a6989586621679544674 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertSym1 a6989586621679544400 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersectSym1 a6989586621679544612 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersperseSym1 a6989586621679545422 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (NubBySym1 a6989586621679544231 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Scanl1Sym1 a6989586621679545217 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Scanr1Sym1 a6989586621679545179 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SortBySym1 a6989586621679544751 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TakeWhileSym1 a6989586621679544574 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnionSym1 a6989586621679544203 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ((\\@#@$$) a6989586621679544792 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ((:@#@$$) a6989586621679050289 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings ((++@#@$$) a6989586621679154364 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679545295 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GenericLengthSym0 :: TyFun [a] i -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (LeftSym0 :: TyFun a (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (CompareSym1 a6989586621679189966 :: TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

SuppressUnusedWarnings (Bool_Sym1 a6989586621679122246 :: TyFun a (Bool ~> a) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DeleteBySym1 a6989586621679544773 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertBySym1 a6989586621679544731 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (EnumFromThenToSym1 a6989586621679414073 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

SuppressUnusedWarnings (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (ConstSym0 :: TyFun a (b ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (SeqSym0 :: TyFun a (b ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

SuppressUnusedWarnings (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings ((/=@#@$$) a6989586621679128030 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((==@#@$$) a6989586621679128025 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((<=@#@$$) a6989586621679189976 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((<@#@$$) a6989586621679189971 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((>=@#@$$) a6989586621679189986 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((>@#@$$) a6989586621679189981 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (EnumFromToSym1 a6989586621679414067 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (MappendSym1 a6989586621679860746 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (MaxSym1 a6989586621679189991 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (MinSym1 a6989586621679189996 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((<>@#@$$) a6989586621679173979 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

SuppressUnusedWarnings (AsTypeOfSym1 a6989586621679154319 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings ((*@#@$$) a6989586621679398578 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings ((+@#@$$) a6989586621679398568 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings ((-@#@$$) a6989586621679398573 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (SubtractSym1 a6989586621679398561 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (PureSym0 :: TyFun a (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (ReturnSym0 :: TyFun a (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (RightSym0 :: TyFun b (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (UnlessSym1 a6989586621680354860 :: TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (WhenSym1 a6989586621679271164 :: TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) Source # 
Instance details

Defined in Control.Applicative.Singletons

SuppressUnusedWarnings (VoidSym0 :: TyFun (f a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings (IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (DefaultEqSym1 a6989586621679129674 :: TyFun k Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((<=?@#@$$) a6989586621679370104 :: TyFun k Bool -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (JoinSym0 :: TyFun (m (m a)) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (ShowTypeSym0 :: TyFun t (ErrorMessage' s) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (LengthSym0 :: TyFun (t a) Natural -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (NullSym0 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ToListSym0 :: TyFun (t a) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MaximumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MinimumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ProductSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (SumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldSym0 :: TyFun (t m) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SingI d => SingI1 (ShowParenSym2 d :: (Symbol ~> Symbol) -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol ~> Symbol). Sing x -> Sing (ShowParenSym2 d x) #

SingI1 (ShowListWithSym1 :: (a ~> (Symbol ~> Symbol)) -> TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a ~> (Symbol ~> Symbol)). Sing x -> Sing (ShowListWithSym1 x) #

SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (SortBySym1 x) #

SingI1 (SortBySym1 :: (a ~> (a ~> Ordering)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (SortBySym1 x) #

SingI1 (InsertBySym1 :: (a ~> (a ~> Ordering)) -> TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (InsertBySym1 x) #

SingI1 (GroupBy1Sym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (GroupBy1Sym1 x) #

SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (NubBySym1 x) #

SingI1 (DeleteFirstsBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (DeleteFirstsBySym1 x) #

SingI1 (IntersectBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (IntersectBySym1 x) #

SingI1 (UnionBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (UnionBySym1 x) #

SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (GroupBySym1 x) #

SingI1 (GroupBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (GroupBySym1 x) #

SingI1 (NubBySym1 :: (a ~> (a ~> Bool)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (NubBySym1 x) #

SingI1 (DeleteBySym1 :: (a ~> (a ~> Bool)) -> TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> Bool)). Sing x -> Sing (DeleteBySym1 x) #

SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanl1Sym1 x) #

SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanr1Sym1 x) #

SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanl1Sym1 x) #

SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanr1Sym1 x) #

SingI1 (Foldl1'Sym1 :: (a ~> (a ~> a)) -> TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Foldl1'Sym1 x) #

SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (BreakSym1 x) #

SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (PartitionSym1 x) #

SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (SpanSym1 x) #

SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (DropWhileSym1 x) #

SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FilterSym1 x) #

SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (TakeWhileSym1 x) #

SingI1 (UntilSym1 :: (a ~> Bool) -> TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (UntilSym1 x) #

SingI1 (FindIndexSym1 :: (a ~> Bool) -> TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FindIndexSym1 x) #

SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (BreakSym1 x) #

SingI1 (PartitionSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (PartitionSym1 x) #

SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (SpanSym1 x) #

SingI1 (FindIndicesSym1 :: (a ~> Bool) -> TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FindIndicesSym1 x) #

SingI1 (DropWhileEndSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (DropWhileEndSym1 x) #

SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (DropWhileSym1 x) #

SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FilterSym1 x) #

SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (TakeWhileSym1 x) #

SFoldable t => SingI1 (MaximumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (MaximumBySym1 x :: TyFun (t a) a -> Type) #

SFoldable t => SingI1 (MinimumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> Ordering)). Sing x -> Sing (MinimumBySym1 x :: TyFun (t a) a -> Type) #

SFoldable t => SingI1 (Foldl1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Foldl1Sym1 x :: TyFun (t a) a -> Type) #

SFoldable t => SingI1 (Foldr1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Foldr1Sym1 x :: TyFun (t a) a -> Type) #

SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (ScanrSym1 x) #

SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (ScanrSym1 x) #

SingI1 (MapMaybeSym1 :: (a ~> Maybe b) -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: a ~> Maybe b). Sing x -> Sing (MapMaybeSym1 x) #

SingI1 (UnfoldSym1 :: (a ~> (b, Maybe a)) -> TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (b, Maybe a)). Sing x -> Sing (UnfoldSym1 x) #

SingI1 (UnfoldrSym1 :: (a ~> (b, Maybe a)) -> TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (b, Maybe a)). Sing x -> Sing (UnfoldrSym1 x) #

SMonadPlus m => SingI1 (MfilterSym1 :: (a ~> Bool) -> TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (MfilterSym1 x :: TyFun (m a) (m a) -> Type) #

SFoldable t => SingI1 (FindSym1 :: (a ~> Bool) -> TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FindSym1 x :: TyFun (t a) (Maybe a) -> Type) #

SFoldable t => SingI1 (AllSym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (AllSym1 x :: TyFun (t a) Bool -> Type) #

SFoldable t => SingI1 (AnySym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (AnySym1 x :: TyFun (t a) Bool -> Type) #

SingI d => SingI1 (UntilSym2 d :: (a ~> a) -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> a). Sing x -> Sing (UntilSym2 d x) #

SOrd b => SingI1 (GroupAllWith1Sym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (GroupAllWith1Sym1 x) #

SEq b => SingI1 (GroupWith1Sym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (GroupWith1Sym1 x) #

SingI1 (MapSym1 :: (a ~> b) -> TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (MapSym1 x) #

SOrd b => SingI1 (GroupAllWithSym1 :: (a ~> b) -> TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (GroupAllWithSym1 x) #

SEq b => SingI1 (GroupWithSym1 :: (a ~> b) -> TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (GroupWithSym1 x) #

SingI1 (MapSym1 :: (a ~> b) -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (MapSym1 x) #

SingI1 (($!@#@$$) :: (a ~> b) -> TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (($!@#@$$) x) #

SingI1 (($@#@$$) :: (a ~> b) -> TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (($@#@$$) x) #

SApplicative m => SingI1 (FilterMSym1 :: (a ~> m Bool) -> TyFun [a] (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> m Bool). Sing x -> Sing (FilterMSym1 x) #

SOrd o => SingI1 (SortWithSym1 :: (a ~> o) -> TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> o). Sing x -> Sing (SortWithSym1 x) #

SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (ScanlSym1 x) #

SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (ScanlSym1 x) #

SingI1 (UnfoldrSym1 :: (b ~> Maybe (a, b)) -> TyFun b [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b ~> Maybe (a, b)). Sing x -> Sing (UnfoldrSym1 x) #

SOrd a => SingI1 (ComparingSym1 :: (b ~> a) -> TyFun b (b ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: b ~> a). Sing x -> Sing (ComparingSym1 x) #

SingI2 (UntilSym2 :: (a ~> Bool) -> (a ~> a) -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: a ~> Bool) (y :: a ~> a). Sing x -> Sing y -> Sing (UntilSym2 x y) #

SingI2 (Either_Sym2 :: (a ~> c) -> (b ~> c) -> TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing2 :: forall (x :: a ~> c) (y :: b ~> c). Sing x -> Sing y -> Sing (Either_Sym2 x y) #

SingI2 (OnSym2 :: (b ~> (b ~> c)) -> (a ~> b) -> TyFun a (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing2 :: forall (x :: b ~> (b ~> c)) (y :: a ~> b). Sing x -> Sing y -> Sing (OnSym2 x y) #

SingI2 ((.@#@$$$) :: (b ~> c) -> (a ~> b) -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: b ~> c) (y :: a ~> b). Sing x -> Sing y -> Sing (x .@#@$$$ y) #

SMonad m => SingI2 ((>=>@#@$$$) :: (a ~> m b) -> (b ~> m c) -> TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing2 :: forall (x :: a ~> m b) (y :: b ~> m c). Sing x -> Sing y -> Sing (x >=>@#@$$$ y) #

SMonad m => SingI2 ((<=<@#@$$$) :: (b ~> m c) -> (a ~> m b) -> TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing2 :: forall (x :: b ~> m c) (y :: a ~> m b). Sing x -> Sing y -> Sing (x <=<@#@$$$ y) #

SingI1 (CurrySym1 :: ((a, b) ~> c) -> TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: (a, b) ~> c). Sing x -> Sing (CurrySym1 x) #

SFoldable t => SingI1 (Foldr'Sym1 :: (a ~> (b ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (Foldr'Sym1 x :: TyFun b (t a ~> b) -> Type) #

SFoldable t => SingI1 (FoldrSym1 :: (a ~> (b ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (FoldrSym1 x :: TyFun b (t a ~> b) -> Type) #

SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (ZipWithSym1 x) #

SingI1 (UncurrySym1 :: (a ~> (b ~> c)) -> TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (UncurrySym1 x) #

SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (ZipWithSym1 x) #

SingI1 (FlipSym1 :: (a ~> (b ~> c)) -> TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (FlipSym1 x) #

SFoldable t => SingI1 (ConcatMapSym1 :: (a ~> [b]) -> TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> [b]). Sing x -> Sing (ConcatMapSym1 x :: TyFun (t a) [b] -> Type) #

SingI d => SingI1 (Maybe_Sym2 d :: (a ~> b) -> TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (Maybe_Sym2 d x) #

SFunctor f => SingI1 (FmapSym1 :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (FmapSym1 x :: TyFun (f a) (f b) -> Type) #

SApplicative f => SingI1 (LiftASym1 :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (LiftASym1 x :: TyFun (f a) (f b) -> Type) #

SFunctor f => SingI1 ((<$>@#@$$) :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing ((<$>@#@$$) x :: TyFun (f a) (f b) -> Type) #

SMonad m => SingI1 ((<$!>@#@$$) :: (a ~> b) -> TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing ((<$!>@#@$$) x :: TyFun (m a) (m b) -> Type) #

STraversable t => SingI1 (FmapDefaultSym1 :: (a ~> b) -> TyFun (t a) (t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (FmapDefaultSym1 x :: TyFun (t a) (t b) -> Type) #

SingI1 (Either_Sym1 :: (a ~> c) -> TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing :: forall (x :: a ~> c). Sing x -> Sing (Either_Sym1 x :: TyFun (b ~> c) (Either a b ~> c) -> Type) #

(SFoldable t, SMonoid m) => SingI1 (FoldMapSym1 :: (a ~> m) -> TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> m). Sing x -> Sing (FoldMapSym1 x :: TyFun (t a) m -> Type) #

(STraversable t, SMonoid m) => SingI1 (FoldMapDefaultSym1 :: (a ~> m) -> TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> m). Sing x -> Sing (FoldMapDefaultSym1 x :: TyFun (t a) m -> Type) #

SMonad m => SingI1 ((=<<@#@$$) :: (a ~> m b) -> TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing ((=<<@#@$$) x) #

SMonad m => SingI1 (LiftMSym1 :: (a1 ~> r) -> TyFun (m a1) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> r). Sing x -> Sing (LiftMSym1 x :: TyFun (m a1) (m r) -> Type) #

SFoldable t => SingI1 (Foldl'Sym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (Foldl'Sym1 x :: TyFun b (t a ~> b) -> Type) #

SFoldable t => SingI1 (FoldlSym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (FoldlSym1 x :: TyFun b (t a ~> b) -> Type) #

SingI1 (OnSym1 :: (b ~> (b ~> c)) -> TyFun (a ~> b) (a ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing :: forall (x :: b ~> (b ~> c)). Sing x -> Sing (OnSym1 x :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) #

SingI1 ((.@#@$$) :: (b ~> c) -> TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: b ~> c). Sing x -> Sing ((.@#@$$) x :: TyFun (a ~> b) (a ~> c) -> Type) #

SingI1 (ZipWith3Sym1 :: (a ~> (b ~> (c ~> d))) -> TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> (c ~> d))). Sing x -> Sing (ZipWith3Sym1 x) #

STraversable t => SingI1 (MapAccumLSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> (a, c))). Sing x -> Sing (MapAccumLSym1 x :: TyFun a (t b ~> (a, t c)) -> Type) #

STraversable t => SingI1 (MapAccumRSym1 :: (a ~> (b ~> (a, c))) -> TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> (a, c))). Sing x -> Sing (MapAccumRSym1 x :: TyFun a (t b ~> (a, t c)) -> Type) #

SApplicative f => SingI1 (LiftA2Sym1 :: (a ~> (b ~> c)) -> TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (LiftA2Sym1 x :: TyFun (f a) (f b ~> f c) -> Type) #

SMonadZip m => SingI1 (MzipWithSym1 :: (a ~> (b ~> c)) -> TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (MzipWithSym1 x :: TyFun (m a) (m b ~> m c) -> Type) #

(SFoldable t, SMonad m) => SingI1 (FoldrMSym1 :: (a ~> (b ~> m b)) -> TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> m b)). Sing x -> Sing (FoldrMSym1 x :: TyFun b (t a ~> m b) -> Type) #

SApplicative m => SingI1 (ZipWithM_Sym1 :: (a ~> (b ~> m c)) -> TyFun [a] ([b] ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> m c)). Sing x -> Sing (ZipWithM_Sym1 x) #

SApplicative m => SingI1 (ZipWithMSym1 :: (a ~> (b ~> m c)) -> TyFun [a] ([b] ~> m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> m c)). Sing x -> Sing (ZipWithMSym1 x) #

SingI d => SingI1 (OnSym2 d :: (a ~> b) -> TyFun a (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (OnSym2 d x) #

SingI d => SingI1 ((.@#@$$$) d :: (a ~> b) -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (d .@#@$$$ x) #

(SFoldable t, SApplicative f) => SingI1 (Traverse_Sym1 :: (a ~> f b) -> TyFun (t a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> f b). Sing x -> Sing (Traverse_Sym1 x :: TyFun (t a) (f ()) -> Type) #

(STraversable t, SApplicative f) => SingI1 (TraverseSym1 :: (a ~> f b) -> TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> f b). Sing x -> Sing (TraverseSym1 x :: TyFun (t a) (f (t b)) -> Type) #

SApplicative m => SingI1 (MapAndUnzipMSym1 :: (a ~> m (b, c)) -> TyFun [a] (m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> m (b, c)). Sing x -> Sing (MapAndUnzipMSym1 x) #

SMonad m => SingI1 ((>=>@#@$$) :: (a ~> m b) -> TyFun (b ~> m c) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing ((>=>@#@$$) x :: TyFun (b ~> m c) (a ~> m c) -> Type) #

(SFoldable t, SMonad m) => SingI1 (MapM_Sym1 :: (a ~> m b) -> TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing (MapM_Sym1 x :: TyFun (t a) (m ()) -> Type) #

(STraversable t, SMonad m) => SingI1 (MapMSym1 :: (a ~> m b) -> TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing (MapMSym1 x :: TyFun (t a) (m (t b)) -> Type) #

SMonad m => SingI1 (LiftM2Sym1 :: (a1 ~> (a2 ~> r)) -> TyFun (m a1) (m a2 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> (a2 ~> r)). Sing x -> Sing (LiftM2Sym1 x :: TyFun (m a1) (m a2 ~> m r) -> Type) #

(SFoldable t, SMonad m) => SingI1 (FoldlMSym1 :: (b ~> (a ~> m b)) -> TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> m b)). Sing x -> Sing (FoldlMSym1 x :: TyFun b (t a ~> m b) -> Type) #

SingI d => SingI1 (Either_Sym2 d :: (b ~> c) -> TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing :: forall (x :: b ~> c). Sing x -> Sing (Either_Sym2 d x) #

SMonad m => SingI1 ((<=<@#@$$) :: (b ~> m c) -> TyFun (a ~> m b) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: b ~> m c). Sing x -> Sing ((<=<@#@$$) x :: TyFun (a ~> m b) (a ~> m c) -> Type) #

SApplicative f => SingI1 (LiftA3Sym1 :: (a ~> (b ~> (c ~> d))) -> TyFun (f a) (f b ~> (f c ~> f d)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> (c ~> d))). Sing x -> Sing (LiftA3Sym1 x :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) #

(SMonad m, SingI d) => SingI1 ((<=<@#@$$$) d :: (a ~> m b) -> TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing (d <=<@#@$$$ x) #

SMonad m => SingI1 (LiftM3Sym1 :: (a1 ~> (a2 ~> (a3 ~> r))) -> TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> (a2 ~> (a3 ~> r))). Sing x -> Sing (LiftM3Sym1 x :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) #

(SMonad m, SingI d) => SingI1 ((>=>@#@$$$) d :: (b ~> m c) -> TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

liftSing :: forall (x :: b ~> m c). Sing x -> Sing (d >=>@#@$$$ x) #

SMonad m => SingI1 (LiftM4Sym1 :: (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) -> TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))). Sing x -> Sing (LiftM4Sym1 x :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) #

SMonad m => SingI1 (LiftM5Sym1 :: (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) -> TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))). Sing x -> Sing (LiftM5Sym1 x :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) #

(SOrd b, SingI d) => SingI (GroupAllWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

(SEq b, SingI d) => SingI (GroupWith1Sym1 d :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWith1Sym1 d) #

(SOrd o, SingI d) => SingI (SortWithSym1 d :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (SortWithSym1 d) #

SingI d => SingI (MapSym1 d :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (MapSym1 d) #

SingI d => SingI (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipSym1 d :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) #

SingI (GetConstSym0 :: TyFun (Const a b) a -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sing :: Sing (GetConstSym0 :: TyFun (Const a b) a -> Type) #

SingI (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) #

SFoldable t => SingI (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) #

SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) #

SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) #

SingI (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) #

SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) #

SingI (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) #

SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) #

SingI d => SingI (Maybe_Sym1 d :: TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym1 d :: TyFun (a ~> b) (Maybe a ~> b) -> Type) #

SFunctor f => SingI (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SApplicative f => SingI (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SFunctor f => SingI ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SMonad m => SingI ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) #

STraversable t => SingI (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) #

SingI d => SingI ((&@#@$$) d :: TyFun (a ~> b) b -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing ((&@#@$$) d :: TyFun (a ~> b) b -> Type) #

SingI (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) #

(SFoldable t, SMonoid m) => SingI (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) #

(STraversable t, SMonoid m) => SingI (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) #

SMonad m => SingI ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) #

SMonad m => SingI (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) #

SFoldable t => SingI (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) #

SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) #

SingI (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) #

SingI ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) #

(SingI d1, SingI d2) => SingI (Bool_Sym2 d1 d2 :: TyFun Bool a -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (Bool_Sym2 d1 d2) #

(SEq a, SingI d) => SingI (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) #

SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) #

SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) #

(SOrd b, SingI d) => SingI (GroupAllWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupAllWithSym1 d) #

(SEq b, SingI d) => SingI (GroupWithSym1 d :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (GroupWithSym1 d) #

(SingI d1, SingI d2) => SingI (DeleteBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteBySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (DeleteFirstsBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DeleteFirstsBySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InsertBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InsertBySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (IntersectBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (IntersectBySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (UnionBySym2 d1 d2 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnionBySym2 d1 d2) #

SingI d => SingI (MapMaybeSym1 d :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (MapMaybeSym1 d) #

SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (MapSym1 d) #

(SApplicative m, SingI d) => SingI (FilterMSym1 d :: TyFun [a] (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (FilterMSym1 d) #

SingI d => SingI (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) #

(SingI d1, SingI d2) => SingI (ShowListWithSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym2 d1 d2) #

(SShow a, SingI d1, SingI d2) => SingI (ShowsPrecSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym2 d1 d2) #

SingI d => SingI (UnfoldSym1 d :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldSym1 d) #

SingI d => SingI (UnfoldrSym1 d :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (UnfoldrSym1 d) #

SingI (ConstSym0 :: TyFun a (Const a b) -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sing :: Sing (ConstSym0 :: TyFun a (Const a b) -> Type) #

SingI (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) #

SFunctor f => SingI ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) #

(SEnum a, SingI d1, SingI d2) => SingI (EnumFromThenToSym2 d1 d2 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromThenToSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (UntilSym2 d1 d2 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym2 d1 d2) #

SingI d => SingI (($!@#@$$) d :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($!@#@$$) d) #

SingI d => SingI (($@#@$$) d :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($@#@$$) d) #

SingI d => SingI (ArgSym1 d :: TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sing :: Sing (ArgSym1 d :: TyFun b (Arg a b) -> Type) #

SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanlSym1 d) #

SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanrSym1 d) #

SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym1 d) #

SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym1 d) #

(SOrd a, SingI d) => SingI (ComparingSym1 d :: TyFun b (b ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (ComparingSym1 d) #

SingI d => SingI (Tuple2Sym1 d :: TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple2Sym1 d :: TyFun b (a, b) -> Type) #

SingI d => SingI (UnfoldrSym1 d :: TyFun b [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnfoldrSym1 d) #

SingI d => SingI (ConstSym1 d :: TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (ConstSym1 d :: TyFun b a -> Type) #

SingI d => SingI (SeqSym1 d :: TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (SeqSym1 d :: TyFun b b -> Type) #

SApplicative f => SingI ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) #

SFunctor f => SingI ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) #

SFunctor f => SingI (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) #

SApplicative f => SingI ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) #

SApplicative f => SingI ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) #

SApplicative f => SingI ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) #

(SAlternative f, SingI d) => SingI ((<|>@#@$$) d :: TyFun (f a) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<|>@#@$$) d) #

SMonad m => SingI (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) #

SMonadZip m => SingI (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) #

SMonad m => SingI ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) #

SMonadZip m => SingI (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) #

SMonad m => SingI ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) #

(SApplicative m, SingI d) => SingI (ReplicateM_Sym1 d :: TyFun (m a) (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ReplicateM_Sym1 d :: TyFun (m a) (m ()) -> Type) #

(SApplicative m, SingI d) => SingI (ReplicateMSym1 d :: TyFun (m a) (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ReplicateMSym1 d :: TyFun (m a) (m [a]) -> Type) #

(SMonadPlus m, SingI d) => SingI (MfilterSym1 d :: TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (MfilterSym1 d :: TyFun (m a) (m a) -> Type) #

(SMonadPlus m, SingI d) => SingI (MplusSym1 d :: TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (MplusSym1 d) #

SingI d => SingI (AsProxyTypeOfSym1 d :: TyFun (proxy a) a -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sing :: Sing (AsProxyTypeOfSym1 d :: TyFun (proxy a) a -> Type) #

(SFoldable t, SingI d) => SingI (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FindSym1 d :: TyFun (t a) (Maybe a) -> Type) #

(SFoldable t, SingI d) => SingI (AllSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AllSym1 d :: TyFun (t a) Bool -> Type) #

(SFoldable t, SingI d) => SingI (AnySym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AnySym1 d :: TyFun (t a) Bool -> Type) #

(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ElemSym1 d :: TyFun (t a) Bool -> Type) #

(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NotElemSym1 d :: TyFun (t a) Bool -> Type) #

(SFoldable t, SingI d) => SingI (Foldl1Sym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl1Sym1 d :: TyFun (t a) a -> Type) #

(SFoldable t, SingI d) => SingI (Foldr1Sym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr1Sym1 d :: TyFun (t a) a -> Type) #

(SFoldable t, SingI d) => SingI (MaximumBySym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MaximumBySym1 d :: TyFun (t a) a -> Type) #

(SFoldable t, SingI d) => SingI (MinimumBySym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MinimumBySym1 d :: TyFun (t a) a -> Type) #

(SFoldable t, SApplicative f) => SingI (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) #

(SFoldable t, SAlternative f) => SingI (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) #

(STraversable t, SApplicative f) => SingI (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) #

(SFoldable t, SMonad m) => SingI (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) #

(SFoldable t, SMonadPlus m) => SingI (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) #

(STraversable t, SMonad m) => SingI (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) #

(SingI c, SingI t) => SingI (IfSym2 c t :: TyFun k k -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym2 c t) #

(forall (a :: k1). SingI a => SingI (f a), (ApplyTyCon :: (k1 -> kr) -> TyFun k1 kr -> Type) ~ (ApplyTyConAux1 :: (k1 -> kr) -> TyFun k1 kr -> Type)) => SingI (TyCon1 f :: TyFun k1 kr -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon1 f) #

SuppressUnusedWarnings (GroupAllWith1Sym1 a6989586621680286976 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupWith1Sym1 a6989586621680286985 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SortWithSym1 a6989586621680286847 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (MapSym1 a6989586621680287251 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ZipSym1 a6989586621680286929 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GetConstSym0 :: TyFun (Const a b) a -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

SuppressUnusedWarnings (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings ((&@#@$$) a6989586621679253960 :: TyFun (a ~> b) b -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

SuppressUnusedWarnings (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

SuppressUnusedWarnings (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

SuppressUnusedWarnings ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (Bool_Sym2 a6989586621679122246 a6989586621679122247 :: TyFun Bool a -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GroupAllWithSym1 a6989586621680287030 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupWithSym1 a6989586621680287039 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DeleteBySym2 a6989586621679544773 a6989586621679544774 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679544763 a6989586621679544764 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertBySym2 a6989586621679544731 a6989586621679544732 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersectBySym2 a6989586621679544588 a6989586621679544589 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnionBySym2 a6989586621679544211 a6989586621679544212 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (MapMaybeSym1 a6989586621679390184 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (MapSym1 a6989586621679154373 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (FilterMSym1 a6989586621680355005 :: TyFun [a] (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ShowListWithSym2 a6989586621679807383 a6989586621679807384 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (UnfoldSym1 a6989586621680287356 :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (UnfoldrSym1 a6989586621680287321 :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ConstSym0 :: TyFun a (Const a b) -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

SuppressUnusedWarnings (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (EnumFromThenToSym2 a6989586621679414073 a6989586621679414074 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (UntilSym2 a6989586621679154281 a6989586621679154282 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (($!@#@$$) a6989586621679154299 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (($@#@$$) a6989586621679154308 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (ArgSym1 a6989586621680159057 :: TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

SuppressUnusedWarnings (ScanlSym1 a6989586621680287221 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanrSym1 a6989586621680287209 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanlSym1 a6989586621679545226 :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ScanrSym1 a6989586621679545199 :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ComparingSym1 a6989586621679189957 :: TyFun b (b ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (UnfoldrSym1 a6989586621679545055 :: TyFun b [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ConstSym1 a6989586621679154354 :: TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (SeqSym1 a6989586621679154272 :: TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<|>@#@$$) a6989586621679271374 :: TyFun (f a) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (IfSym2 a6989586621679124436 a6989586621679124437 :: TyFun k k -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

SuppressUnusedWarnings ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

SuppressUnusedWarnings ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (ReplicateM_Sym1 a6989586621680354872 :: TyFun (m a) (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ReplicateMSym1 a6989586621680354894 :: TyFun (m a) (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (MfilterSym1 a6989586621680354827 :: TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (MplusSym1 a6989586621679271380 :: TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (AsProxyTypeOfSym1 a6989586621679900552 :: TyFun (proxy a) a -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

SuppressUnusedWarnings (FindSym1 a6989586621679922286 :: TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MaximumBySym1 a6989586621679922335 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MinimumBySym1 a6989586621679922315 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SingI d => SingI (ZipWithSym1 d :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipWithSym1 d) #

SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) #

STraversable t => SingI (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) #

STraversable t => SingI (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) #

SApplicative f => SingI (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) #

SMonadZip m => SingI (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) #

(SFoldable t, SMonad m) => SingI (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) #

SApplicative m => SingI (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) #

SApplicative m => SingI (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) #

SingI d => SingI (OnSym1 d :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym1 d :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) #

SingI d => SingI ((.@#@$$) d :: TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((.@#@$$) d :: TyFun (a ~> b) (a ~> c) -> Type) #

(SFunctor f, SingI d) => SingI ((<&>@#@$$) d :: TyFun (a ~> b) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<&>@#@$$) d :: TyFun (a ~> b) (f b) -> Type) #

(SFoldable t, SApplicative f) => SingI (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) #

(STraversable t, SApplicative f) => SingI (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) #

SApplicative m => SingI (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) #

SMonad m => SingI ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) #

(SFoldable t, SMonad m) => SingI (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) #

(STraversable t, SMonad m) => SingI (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) #

(SMonad m, SingI d) => SingI ((>>=@#@$$) d :: TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>=@#@$$) d :: TyFun (a ~> m b) (m b) -> Type) #

SMonad m => SingI (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) #

(SFoldable t, SMonad m) => SingI (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) #

SingI d => SingI (Either_Sym1 d :: TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym1 d :: TyFun (b ~> c) (Either a b ~> c) -> Type) #

SMonad m => SingI ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) #

(SingI d1, SingI d2) => SingI (Maybe_Sym2 d1 d2 :: TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym2 d1 d2) #

SingI d => SingI (UncurrySym1 d :: TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (UncurrySym1 d) #

SingI (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) #

(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanlSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ScanrSym2 d1 d2) #

SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym1 d) #

(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym2 d1 d2) #

SingI d => SingI (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) #

SingI (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) #

SingI d => SingI (CurrySym1 d :: TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym1 d) #

(SOrd a, SingI d1, SingI d2) => SingI (ComparingSym2 d1 d2 :: TyFun b Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (ComparingSym2 d1 d2) #

SingI d => SingI (FlipSym1 d :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym1 d) #

SingI d => SingI (Tuple3Sym1 d :: TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym1 d :: TyFun b (c ~> (a, b, c)) -> Type) #

(SFoldable t, SingI d) => SingI (Foldl'Sym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl'Sym1 d :: TyFun b (t a ~> b) -> Type) #

(SFoldable t, SingI d) => SingI (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) #

(SFoldable t, SingI d) => SingI (Foldr'Sym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr'Sym1 d :: TyFun b (t a ~> b) -> Type) #

(SFoldable t, SingI d) => SingI (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) #

(SFunctor f, SingI d) => SingI (($>@#@$$) d :: TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing (($>@#@$$) d :: TyFun b (f b) -> Type) #

(SApplicative f, SingI d) => SingI ((<**>@#@$$) d :: TyFun (f (a ~> b)) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<**>@#@$$) d :: TyFun (f (a ~> b)) (f b) -> Type) #

SingI (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sing :: Sing (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) #

SingI (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sing :: Sing (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) #

(SApplicative f, SingI d) => SingI ((<*>@#@$$) d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*>@#@$$) d) #

(SFunctor f, SingI d) => SingI (FmapSym1 d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (FmapSym1 d :: TyFun (f a) (f b) -> Type) #

(SApplicative f, SingI d) => SingI (LiftASym1 d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftASym1 d :: TyFun (f a) (f b) -> Type) #

(SFunctor f, SingI d) => SingI ((<$>@#@$$) d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<$>@#@$$) d :: TyFun (f a) (f b) -> Type) #

(SFunctor f, SingI d) => SingI ((<$@#@$$) d :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<$@#@$$) d :: TyFun (f b) (f a) -> Type) #

(SApplicative f, SingI d) => SingI ((<*@#@$$) d :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*@#@$$) d :: TyFun (f b) (f a) -> Type) #

(SApplicative f, SingI d) => SingI ((*>@#@$$) d :: TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((*>@#@$$) d :: TyFun (f b) (f b) -> Type) #

SingI (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sing :: Sing (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) #

(SMonad m, SingI d) => SingI ((<$!>@#@$$) d :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((<$!>@#@$$) d :: TyFun (m a) (m b) -> Type) #

(SMonad m, SingI d) => SingI ((=<<@#@$$) d :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((=<<@#@$$) d) #

(SMonad m, SingI d) => SingI (ApSym1 d :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (ApSym1 d) #

(SMonad m, SingI d) => SingI (LiftMSym1 d :: TyFun (m a1) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftMSym1 d :: TyFun (m a1) (m r) -> Type) #

(SMonadZip m, SingI d) => SingI (MzipSym1 d :: TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipSym1 d :: TyFun (m b) (m (a, b)) -> Type) #

(SMonad m, SingI d) => SingI ((>>@#@$$) d :: TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>@#@$$) d :: TyFun (m b) (m b) -> Type) #

(SFoldable t, SApplicative f) => SingI (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) #

(STraversable t, SApplicative f) => SingI (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) #

(SFoldable t, SMonad m) => SingI (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) #

(STraversable t, SMonad m) => SingI (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) #

(SFoldable t, SingI d) => SingI (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) #

(SFoldable t, SMonoid m, SingI d) => SingI (FoldMapSym1 d :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldMapSym1 d :: TyFun (t a) m -> Type) #

(STraversable t, SMonoid m, SingI d) => SingI (FoldMapDefaultSym1 d :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (FoldMapDefaultSym1 d :: TyFun (t a) m -> Type) #

(STraversable t, SingI d) => SingI (FmapDefaultSym1 d :: TyFun (t a) (t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (FmapDefaultSym1 d :: TyFun (t a) (t b) -> Type) #

(forall (a :: k1) (b :: k2). (SingI a, SingI b) => SingI (f a b), (ApplyTyCon :: (k2 -> kr) -> TyFun k2 kr -> Type) ~ (ApplyTyConAux1 :: (k2 -> kr) -> TyFun k2 kr -> Type)) => SingI (TyCon2 f :: TyFun k1 (k2 ~> kr) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon2 f) #

SuppressUnusedWarnings (ZipWithSym1 a6989586621680286918 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

SuppressUnusedWarnings (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (OnSym1 a6989586621679253973 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

SuppressUnusedWarnings ((.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings ((<&>@#@$$) a6989586621679357509 :: TyFun (a ~> b) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings ((>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

SuppressUnusedWarnings ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Maybe_Sym2 a6989586621679387993 a6989586621679387994 :: TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (UncurrySym1 a6989586621679147653 :: TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ScanlSym2 a6989586621680287221 a6989586621680287222 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanrSym2 a6989586621680287209 a6989586621680287210 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWithSym1 a6989586621679544962 :: TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ScanlSym2 a6989586621679545226 a6989586621679545227 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ScanrSym2 a6989586621679545199 a6989586621679545200 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (CurrySym1 a6989586621679147661 :: TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (ComparingSym2 a6989586621679189957 a6989586621679189958 :: TyFun b Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (FlipSym1 a6989586621679154327 :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Foldl'Sym1 a6989586621679922542 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr'Sym1 a6989586621679922528 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (($>@#@$$) a6989586621679357502 :: TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings ((<**>@#@$$) a6989586621679271211 :: TyFun (f (a ~> b)) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

SuppressUnusedWarnings (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

SuppressUnusedWarnings ((<*>@#@$$) a6989586621679271255 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftASym1 a6989586621679271200 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings ((<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

SuppressUnusedWarnings ((<$!>@#@$$) a6989586621680354845 :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings ((=<<@#@$$) a6989586621679271176 :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (ApSym1 a6989586621679270990 :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftMSym1 a6989586621679271151 :: TyFun (m a1) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MzipSym1 a6989586621680264763 :: TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

SuppressUnusedWarnings ((>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SingI (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sing :: Sing (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) #

(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing (ZipWithSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (Either_Sym2 d1 d2 :: TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym2 d1 d2) #

SApplicative f => SingI (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) #

(SFoldable t, SApplicative f, SingI d) => SingI (For_Sym1 d :: TyFun (a ~> f b) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (For_Sym1 d :: TyFun (a ~> f b) (f ()) -> Type) #

(STraversable t, SApplicative f, SingI d) => SingI (ForSym1 d :: TyFun (a ~> f b) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (ForSym1 d :: TyFun (a ~> f b) (f (t b)) -> Type) #

(SMonad m, SingI d) => SingI ((<=<@#@$$) d :: TyFun (a ~> m b) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((<=<@#@$$) d :: TyFun (a ~> m b) (a ~> m c) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (ForM_Sym1 d :: TyFun (a ~> m b) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ForM_Sym1 d :: TyFun (a ~> m b) (m ()) -> Type) #

(STraversable t, SMonad m, SingI d) => SingI (ForMSym1 d :: TyFun (a ~> m b) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (ForMSym1 d :: TyFun (a ~> m b) (m (t b)) -> Type) #

SMonad m => SingI (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) #

(SMonad m, SingI d) => SingI ((>=>@#@$$) d :: TyFun (b ~> m c) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing ((>=>@#@$$) d :: TyFun (b ~> m c) (a ~> m c) -> Type) #

SingI (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) #

SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym1 d2) #

(SApplicative m, SingI d) => SingI (ZipWithM_Sym1 d :: TyFun [a] ([b] ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithM_Sym1 d) #

(SApplicative m, SingI d) => SingI (ZipWithMSym1 d :: TyFun [a] ([b] ~> m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithMSym1 d) #

(SApplicative m, SingI d) => SingI (MapAndUnzipMSym1 d :: TyFun [a] (m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (MapAndUnzipMSym1 d) #

(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) #

(SingI d1, SingI d2) => SingI (OnSym2 d1 d2 :: TyFun a (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym2 d1 d2) #

SingI (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) #

(STraversable t, SingI d) => SingI (MapAccumLSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumLSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) #

(STraversable t, SingI d) => SingI (MapAccumRSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumRSym1 d :: TyFun a (t b ~> (a, t c)) -> Type) #

(SingI d1, SingI d2) => SingI (d1 .@#@$$$ d2 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (d1 .@#@$$$ d2) #

(SingI d1, SingI d2) => SingI (FlipSym2 d1 d2 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym2 d1 d2) #

SingI d1 => SingI (Tuple4Sym1 d1 :: TyFun b (c ~> (d2 ~> (a, b, c, d2))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym1 d1 :: TyFun b (c ~> (d2 ~> (a, b, c, d2))) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (FoldlMSym1 d :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlMSym1 d :: TyFun b (t a ~> m b) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (FoldrMSym1 d :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrMSym1 d :: TyFun b (t a ~> m b) -> Type) #

(SingI d1, SingI d2) => SingI (CurrySym2 d1 d2 :: TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym2 d1 d2) #

(SingI d1, SingI d2) => SingI (Tuple3Sym2 d1 d2 :: TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym2 d1 d2 :: TyFun c (a, b, c) -> Type) #

(SApplicative f, SingI d) => SingI (LiftA2Sym1 d :: TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym1 d :: TyFun (f a) (f b ~> f c) -> Type) #

SingI (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sing :: Sing (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) #

SingI d => SingI (PairSym1 d :: TyFun (g a) (Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sing :: Sing (PairSym1 d :: TyFun (g a) (Product f g a) -> Type) #

(SMonadZip m, SingI d) => SingI (MzipWithSym1 d :: TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym1 d :: TyFun (m a) (m b ~> m c) -> Type) #

(SMonad m, SingI d) => SingI (LiftM2Sym1 d :: TyFun (m a1) (m a2 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM2Sym1 d :: TyFun (m a1) (m a2 ~> m r) -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (Foldl'Sym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl'Sym2 d1 d2 :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (Foldr'Sym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr'Sym2 d1 d2 :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) #

(SFoldable t, SApplicative f, SingI d) => SingI (Traverse_Sym1 d :: TyFun (t a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Traverse_Sym1 d :: TyFun (t a) (f ()) -> Type) #

(STraversable t, SApplicative f, SingI d) => SingI (TraverseSym1 d :: TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (TraverseSym1 d :: TyFun (t a) (f (t b)) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (MapM_Sym1 d :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MapM_Sym1 d :: TyFun (t a) (m ()) -> Type) #

(STraversable t, SMonad m, SingI d) => SingI (MapMSym1 d :: TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapMSym1 d :: TyFun (t a) (m (t b)) -> Type) #

(forall (a :: k1) (b :: k2) (c :: k3). (SingI a, SingI b, SingI c) => SingI (f a b c), (ApplyTyCon :: (k3 -> kr) -> TyFun k3 kr -> Type) ~ (ApplyTyConAux1 :: (k3 -> kr) -> TyFun k3 kr -> Type)) => SingI (TyCon3 f :: TyFun k1 (k2 ~> (k3 ~> kr)) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon3 f) #

SuppressUnusedWarnings (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

SuppressUnusedWarnings (ZipWithSym2 a6989586621680286918 a6989586621680286919 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Either_Sym2 a6989586621679259290 a6989586621679259291 :: TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

SuppressUnusedWarnings (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (For_Sym1 a6989586621679922460 :: TyFun (a ~> f b) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings ((<=<@#@$$) a6989586621680354976 :: TyFun (a ~> m b) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ForM_Sym1 a6989586621679922440 :: TyFun (a ~> m b) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((>=>@#@$$) a6989586621680354988 :: TyFun (b ~> m c) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679544947 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWithM_Sym1 a6989586621680354943 :: TyFun [a] ([b] ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ZipWithMSym1 a6989586621680354953 :: TyFun [a] ([b] ~> m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (MapAndUnzipMSym1 a6989586621680354962 :: TyFun [a] (m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Zip4Sym1 a6989586621679656286 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWithSym2 a6989586621679544962 a6989586621679544963 :: TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (OnSym2 a6989586621679253973 a6989586621679253974 :: TyFun a (a ~> c) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

SuppressUnusedWarnings (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (a6989586621679154339 .@#@$$$ a6989586621679154340 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (FlipSym2 a6989586621679154327 a6989586621679154328 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (FoldlMSym1 a6989586621679922477 :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrMSym1 a6989586621679922495 :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (CurrySym2 a6989586621679147661 a6989586621679147662 :: TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

SuppressUnusedWarnings (PairSym1 a6989586621680392419 :: TyFun (g a) (Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

SuppressUnusedWarnings (MzipWithSym1 a6989586621680264769 :: TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

SuppressUnusedWarnings (LiftM2Sym1 a6989586621679271130 :: TyFun (m a1) (m a2 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (Foldl'Sym2 a6989586621679922542 a6989586621679922543 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr'Sym2 a6989586621679922528 a6989586621679922529 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Traverse_Sym1 a6989586621679922469 :: TyFun (t a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SMonad m => SingI (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) #

SingI (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) #

(SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym2 d2 d3) #

(SApplicative m, SingI d1, SingI d2) => SingI (ZipWithM_Sym2 d1 d2 :: TyFun [b] (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithM_Sym2 d1 d2) #

(SApplicative m, SingI d1, SingI d2) => SingI (ZipWithMSym2 d1 d2 :: TyFun [b] (m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (ZipWithMSym2 d1 d2) #

SingI (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (OnSym3 d1 d2 d3 :: TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

Methods

sing :: Sing (OnSym3 d1 d2 d3) #

(SMonad m, SingI d1, SingI d2) => SingI (d1 <=<@#@$$$ d2 :: TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (d1 <=<@#@$$$ d2) #

(SMonad m, SingI d1, SingI d2) => SingI (d1 >=>@#@$$$ d2 :: TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

sing :: Sing (d1 >=>@#@$$$ d2) #

SingI d1 => SingI (Tuple5Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (a, b, c, d2, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (a, b, c, d2, e)))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple4Sym2 d1 d2 :: TyFun c (d3 ~> (a, b, c, d3)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym2 d1 d2 :: TyFun c (d3 ~> (a, b, c, d3)) -> Type) #

(SApplicative f, SingI d2) => SingI (LiftA3Sym1 d2 :: TyFun (f a) (f b ~> (f c ~> f d1)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA3Sym1 d2 :: TyFun (f a) (f b ~> (f c ~> f d1)) -> Type) #

(SApplicative f, SingI d1, SingI d2) => SingI (LiftA2Sym2 d1 d2 :: TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym2 d1 d2) #

(SMonad m, SingI d) => SingI (LiftM3Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM3Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) #

(SMonad m, SingI d1, SingI d2) => SingI (LiftM2Sym2 d1 d2 :: TyFun (m a2) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM2Sym2 d1 d2) #

(SMonadZip m, SingI d1, SingI d2) => SingI (MzipWithSym2 d1 d2 :: TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

Methods

sing :: Sing (MzipWithSym2 d1 d2) #

(SFoldable t, SMonad m, SingI d1, SingI d2) => SingI (FoldlMSym2 d1 d2 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlMSym2 d1 d2 :: TyFun (t a) (m b) -> Type) #

(SFoldable t, SMonad m, SingI d1, SingI d2) => SingI (FoldrMSym2 d1 d2 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrMSym2 d1 d2 :: TyFun (t a) (m b) -> Type) #

(STraversable t, SingI d1, SingI d2) => SingI (MapAccumLSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumLSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) #

(STraversable t, SingI d1, SingI d2) => SingI (MapAccumRSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapAccumRSym2 d1 d2 :: TyFun (t b) (a, t c) -> Type) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4). (SingI a, SingI b, SingI c, SingI d) => SingI (f a b c d), (ApplyTyCon :: (k4 -> kr) -> TyFun k4 kr -> Type) ~ (ApplyTyConAux1 :: (k4 -> kr) -> TyFun k4 kr -> Type)) => SingI (TyCon4 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> kr))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon4 f) #

SuppressUnusedWarnings (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith4Sym1 a6989586621679656166 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym1 a6989586621679656263 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679544947 a6989586621679544948 :: TyFun [b] ([c] ~> [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWithM_Sym2 a6989586621680354943 a6989586621680354944 :: TyFun [b] (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ZipWithMSym2 a6989586621680354953 a6989586621680354954 :: TyFun [b] (m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Zip4Sym2 a6989586621679656286 a6989586621679656287 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (OnSym3 a6989586621679253973 a6989586621679253974 a6989586621679253975 :: TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

SuppressUnusedWarnings (a6989586621680354976 <=<@#@$$$ a6989586621680354977 :: TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (a6989586621680354988 >=>@#@$$$ a6989586621680354989 :: TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftA3Sym1 a6989586621679271189 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftA2Sym2 a6989586621679271261 a6989586621679271262 :: TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM3Sym1 a6989586621679271100 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM2Sym2 a6989586621679271130 a6989586621679271131 :: TyFun (m a2) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MzipWithSym2 a6989586621680264769 a6989586621680264770 :: TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

SuppressUnusedWarnings (FoldlMSym2 a6989586621679922477 a6989586621679922478 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrMSym2 a6989586621679922495 a6989586621679922496 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SMonad m => SingI (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) #

SingI (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) #

(SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym3 d2 d3 d4) #

SingI (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) #

SingI d1 => SingI (Tuple6Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f))))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple5Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (a, b, c, d3, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (a, b, c, d3, e))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple4Sym3 d1 d2 d3 :: TyFun d4 (a, b, c, d4) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym3 d1 d2 d3 :: TyFun d4 (a, b, c, d4) -> Type) #

(SApplicative f, SingI d2, SingI d3) => SingI (LiftA3Sym2 d2 d3 :: TyFun (f b) (f c ~> f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA3Sym2 d2 d3) #

(SMonad m, SingI d) => SingI (LiftM4Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) #

(SMonad m, SingI d1, SingI d2) => SingI (LiftM3Sym2 d1 d2 :: TyFun (m a2) (m a3 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM3Sym2 d1 d2) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5). (SingI a, SingI b, SingI c, SingI d, SingI e) => SingI (f a b c d e), (ApplyTyCon :: (k5 -> kr) -> TyFun k5 kr -> Type) ~ (ApplyTyConAux1 :: (k5 -> kr) -> TyFun k5 kr -> Type)) => SingI (TyCon5 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> kr)))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon5 f) #

SuppressUnusedWarnings (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith5Sym1 a6989586621679656143 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym1 a6989586621679656235 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith4Sym2 a6989586621679656166 a6989586621679656167 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym2 a6989586621679656263 a6989586621679656264 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949 :: TyFun [c] [d] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip4Sym3 a6989586621679656286 a6989586621679656287 a6989586621679656288 :: TyFun [d] [(a, b, c, d)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftA3Sym2 a6989586621679271189 a6989586621679271190 :: TyFun (f b) (f c ~> f d) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM4Sym1 a6989586621679271061 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM3Sym2 a6989586621679271100 a6989586621679271101 :: TyFun (m a2) (m a3 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SingI d1 => SingI (Tuple7Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple6Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (a, b, c, d3, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (a, b, c, d3, e, f)))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple5Sym3 d1 d2 d3 :: TyFun d4 (e ~> (a, b, c, d4, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym3 d1 d2 d3 :: TyFun d4 (e ~> (a, b, c, d4, e)) -> Type) #

(SApplicative f, SingI d2, SingI d3, SingI d4) => SingI (LiftA3Sym3 d2 d3 d4 :: TyFun (f c) (f d1) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA3Sym3 d2 d3 d4) #

(SMonad m, SingI d) => SingI (LiftM5Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym1 d :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) #

(SMonad m, SingI d1, SingI d2) => SingI (LiftM4Sym2 d1 d2 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym2 d1 d2) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI (LiftM3Sym3 d1 d2 d3 :: TyFun (m a3) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM3Sym3 d1 d2 d3) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f') => SingI (f a b c d e f'), (ApplyTyCon :: (k6 -> kr) -> TyFun k6 kr -> Type) ~ (ApplyTyConAux1 :: (k6 -> kr) -> TyFun k6 kr -> Type)) => SingI (TyCon6 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> kr))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon6 f) #

SuppressUnusedWarnings (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym1 a6989586621679656116 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym1 a6989586621679656202 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith5Sym2 a6989586621679656143 a6989586621679656144 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym2 a6989586621679656235 a6989586621679656236 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith4Sym3 a6989586621679656166 a6989586621679656167 a6989586621679656168 :: TyFun [c] ([d] ~> [e]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym3 a6989586621679656263 a6989586621679656264 a6989586621679656265 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftA3Sym3 a6989586621679271189 a6989586621679271190 a6989586621679271191 :: TyFun (f c) (f d) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM5Sym1 a6989586621679271013 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM4Sym2 a6989586621679271061 a6989586621679271062 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM3Sym3 a6989586621679271100 a6989586621679271101 a6989586621679271102 :: TyFun (m a3) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

(SingI d1, SingI d2) => SingI (Tuple7Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g))))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple6Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (a, b, c, d4, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (a, b, c, d4, e, f))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple5Sym4 d1 d2 d3 d5 :: TyFun e (a, b, c, d4, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym4 d1 d2 d3 d5 :: TyFun e (a, b, c, d4, e) -> Type) #

(SMonad m, SingI d1, SingI d2) => SingI (LiftM5Sym2 d1 d2 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym2 d1 d2) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI (LiftM4Sym3 d1 d2 d3 :: TyFun (m a3) (m a4 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym3 d1 d2 d3) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6) (g :: k7). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f', SingI g) => SingI (f a b c d e f' g), (ApplyTyCon :: (k7 -> kr) -> TyFun k7 kr -> Type) ~ (ApplyTyConAux1 :: (k7 -> kr) -> TyFun k7 kr -> Type)) => SingI (TyCon7 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> kr)))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon7 f) #

SuppressUnusedWarnings (ZipWith7Sym1 a6989586621679656085 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym2 a6989586621679656116 a6989586621679656117 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym2 a6989586621679656202 a6989586621679656203 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith5Sym3 a6989586621679656143 a6989586621679656144 a6989586621679656145 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym3 a6989586621679656235 a6989586621679656236 a6989586621679656237 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith4Sym4 a6989586621679656166 a6989586621679656167 a6989586621679656168 a6989586621679656169 :: TyFun [d] [e] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym4 a6989586621679656263 a6989586621679656264 a6989586621679656265 a6989586621679656266 :: TyFun [e] [(a, b, c, d, e)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftM5Sym2 a6989586621679271013 a6989586621679271014 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM4Sym3 a6989586621679271061 a6989586621679271062 a6989586621679271063 :: TyFun (m a3) (m a4 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

(SingI d1, SingI d2, SingI d3) => SingI (Tuple7Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (g ~> (a, b, c, d4, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (g ~> (a, b, c, d4, e, f, g)))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple6Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) #

(SMonad m, SingI d1, SingI d2, SingI d3) => SingI (LiftM5Sym3 d1 d2 d3 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym3 d1 d2 d3) #

(SMonad m, SingI d1, SingI d2, SingI d3, SingI d4) => SingI (LiftM4Sym4 d1 d2 d3 d4 :: TyFun (m a4) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM4Sym4 d1 d2 d3 d4) #

(forall (a :: k1) (b :: k2) (c :: k3) (d :: k4) (e :: k5) (f' :: k6) (g :: k7) (h :: k8). (SingI a, SingI b, SingI c, SingI d, SingI e, SingI f', SingI g, SingI h) => SingI (f a b c d e f' g h), (ApplyTyCon :: (k8 -> kr) -> TyFun k8 kr -> Type) ~ (ApplyTyConAux1 :: (k8 -> kr) -> TyFun k8 kr -> Type)) => SingI (TyCon8 f :: TyFun k1 (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k8 ~> kr))))))) -> Type) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing (TyCon8 f) #

SuppressUnusedWarnings (ZipWith7Sym2 a6989586621679656085 a6989586621679656086 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym3 a6989586621679656116 a6989586621679656117 a6989586621679656118 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym3 a6989586621679656202 a6989586621679656203 a6989586621679656204 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith5Sym4 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 :: TyFun [d] ([e] ~> [f]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym4 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftM5Sym3 a6989586621679271013 a6989586621679271014 a6989586621679271015 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM4Sym4 a6989586621679271061 a6989586621679271062 a6989586621679271063 a6989586621679271064 :: TyFun (m a4) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple7Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI (Tuple6Sym5 d1 d2 d3 d5 d6 :: TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym5 d1 d2 d3 d5 d6 :: TyFun f (a, b, c, d4, e, f) -> Type) #

(SMonad m, SingI d1, SingI d2, SingI d3, SingI d4) => SingI (LiftM5Sym4 d1 d2 d3 d4 :: TyFun (m a4) (m a5 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym4 d1 d2 d3 d4) #

SuppressUnusedWarnings (ZipWith7Sym3 a6989586621679656085 a6989586621679656086 a6989586621679656087 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym4 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym4 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith5Sym5 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 a6989586621679656147 :: TyFun [e] [f] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym5 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 a6989586621679656239 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftM5Sym4 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 :: TyFun (m a4) (m a5 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI (Tuple7Sym5 d1 d2 d3 d5 d6 :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym5 d1 d2 d3 d5 d6 :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

(SMonad m, SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (LiftM5Sym5 d1 d2 d3 d4 d5 :: TyFun (m a5) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftM5Sym5 d1 d2 d3 d4 d5) #

SuppressUnusedWarnings (ZipWith7Sym4 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym5 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 :: TyFun [e] ([f] ~> [g]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym5 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftM5Sym5 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 a6989586621679271017 :: TyFun (m a5) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6, SingI d7) => SingI (Tuple7Sym6 d1 d2 d3 d5 d6 d7 :: TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym6 d1 d2 d3 d5 d6 d7 :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

SuppressUnusedWarnings (ZipWith7Sym5 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym6 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 a6989586621679656121 :: TyFun [f] [g] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym6 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 a6989586621679656207 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (ZipWith7Sym6 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 :: TyFun [f] ([g] ~> [h]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith7Sym7 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 a6989586621679656091 :: TyFun [g] [h] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TyCon f :: k1 ~> k3) (x :: k1) # 
Instance details

Defined in Data.Singletons

type Apply (TyCon f :: k1 ~> k3) (x :: k1) = ApplyTyCon f @@ x
type Apply DivSym0 (a6989586621679378709 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply DivSym0 (a6989586621679378709 :: Natural) = DivSym1 a6989586621679378709
type Apply ModSym0 (a6989586621679379154 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply ModSym0 (a6989586621679379154 :: Natural) = ModSym1 a6989586621679379154
type Apply QuotSym0 (a6989586621679379824 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply QuotSym0 (a6989586621679379824 :: Natural) = QuotSym1 a6989586621679379824
type Apply RemSym0 (a6989586621679379813 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply RemSym0 (a6989586621679379813 :: Natural) = RemSym1 a6989586621679379813
type Apply (^@#@$) (a6989586621679369666 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (^@#@$) (a6989586621679369666 :: Natural) = (^@#@$$) a6989586621679369666
type Apply DivModSym0 (a6989586621679379842 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply DivModSym0 (a6989586621679379842 :: Natural) = DivModSym1 a6989586621679379842
type Apply QuotRemSym0 (a6989586621679379835 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply QuotRemSym0 (a6989586621679379835 :: Natural) = QuotRemSym1 a6989586621679379835
type Apply ShowParenSym0 (a6989586621679807346 :: Bool) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowParenSym0 (a6989586621679807346 :: Bool) = ShowParenSym1 a6989586621679807346
type Apply (&&@#@$) (a6989586621679123502 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (&&@#@$) (a6989586621679123502 :: Bool) = (&&@#@$$) a6989586621679123502
type Apply (||@#@$) (a6989586621679123865 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (||@#@$) (a6989586621679123865 :: Bool) = (||@#@$$) a6989586621679123865
type Apply ConsSymbolSym0 (a6989586621679381116 :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply ConsSymbolSym0 (a6989586621679381116 :: Char) = ConsSymbolSym1 a6989586621679381116
type Apply ShowCharSym0 (a6989586621679807375 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621679807375 :: Char) = ShowCharSym1 a6989586621679807375
type Apply ShowStringSym0 (a6989586621679807364 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621679807364 :: Symbol) = ShowStringSym1 a6989586621679807364
type Apply (~>@#@$) (x :: Type) # 
Instance details

Defined in Data.Singletons

type Apply (~>@#@$) (x :: Type) = (~>@#@$$) x
type Apply (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287146 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SplitAtSym0 :: TyFun Natural (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287146 :: Natural) = SplitAtSym1 a6989586621680287146 :: TyFun (NonEmpty a) ([a], [a]) -> Type
type Apply (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287155 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287155 :: Natural) = DropSym1 a6989586621680287155 :: TyFun (NonEmpty a) [a] -> Type
type Apply (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287164 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeSym0 :: TyFun Natural (NonEmpty a ~> [a]) -> Type) (a6989586621680287164 :: Natural) = TakeSym1 a6989586621680287164 :: TyFun (NonEmpty a) [a] -> Type
type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679544425 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679544425 :: Natural) = SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type
type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544432 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544432 :: Natural) = DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type
type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544445 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544445 :: Natural) = TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type
type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807409 :: Natural) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807409 :: Natural) = ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type
type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679544286 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679544286 :: Natural) = ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type
type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621680354860 :: Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621680354860 :: Bool) = UnlessSym1 a6989586621680354860 :: TyFun (f ()) (f ()) -> Type
type Apply (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621679271164 :: Bool) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (WhenSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621679271164 :: Bool) = WhenSym1 a6989586621679271164 :: TyFun (f ()) (f ()) -> Type
type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679124436 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679124436 :: Bool) = IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type
type Apply ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287295 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((<|@#@$) :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287295 :: a) = (<|@#@$$) a6989586621680287295
type Apply (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287288 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287288 :: a) = ConsSym1 a6989586621680287288
type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287177 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym0 :: TyFun a (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287177 :: a) = IntersperseSym1 a6989586621680287177
type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679390214 :: a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (FromMaybeSym0 :: TyFun a (Maybe a ~> a) -> Type) (a6989586621679390214 :: a) = FromMaybeSym1 a6989586621679390214
type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621680287232 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InsertSym0 :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621680287232 :: a) = InsertSym1 a6989586621680287232
type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679050362 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$) :: TyFun a ([a] ~> NonEmpty a) -> Type) (a6989586621679050362 :: a) = (:|@#@$$) a6989586621679050362
type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679544658 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndexSym0 :: TyFun a ([a] ~> Maybe Natural) -> Type) (a6989586621679544658 :: a) = ElemIndexSym1 a6989586621679544658
type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679544649 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndicesSym0 :: TyFun a ([a] ~> [Natural]) -> Type) (a6989586621679544649 :: a) = ElemIndicesSym1 a6989586621679544649
type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544803 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544803 :: a) = DeleteSym1 a6989586621679544803
type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544400 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544400 :: a) = InsertSym1 a6989586621679544400
type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679545422 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersperseSym0 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679545422 :: a) = IntersperseSym1 a6989586621679545422
type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679050289 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679050289 :: a) = (:@#@$$) a6989586621679050289
type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807401 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807401 :: a) = ShowsSym1 a6989586621679807401
type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679189966 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679189966 :: a) = CompareSym1 a6989586621679189966
type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679122246 :: a) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym0 :: TyFun a (a ~> (Bool ~> a)) -> Type) (a6989586621679122246 :: a) = Bool_Sym1 a6989586621679122246
type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679414073 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679414073 :: a) = EnumFromThenToSym1 a6989586621679414073
type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128030 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128030 :: a) = (/=@#@$$) a6989586621679128030
type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128025 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128025 :: a) = (==@#@$$) a6989586621679128025
type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189976 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189976 :: a) = (<=@#@$$) a6989586621679189976
type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189971 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189971 :: a) = (<@#@$$) a6989586621679189971
type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189986 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189986 :: a) = (>=@#@$$) a6989586621679189986
type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189981 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189981 :: a) = (>@#@$$) a6989586621679189981
type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414067 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414067 :: a) = EnumFromToSym1 a6989586621679414067
type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679860746 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679860746 :: a) = MappendSym1 a6989586621679860746
type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189991 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189991 :: a) = MaxSym1 a6989586621679189991
type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189996 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189996 :: a) = MinSym1 a6989586621679189996
type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679173979 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679173979 :: a) = (<>@#@$$) a6989586621679173979
type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679154319 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679154319 :: a) = AsTypeOfSym1 a6989586621679154319
type Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398578 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398578 :: a) = (*@#@$$) a6989586621679398578
type Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398568 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398568 :: a) = (+@#@$$) a6989586621679398568
type Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398573 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398573 :: a) = (-@#@$$) a6989586621679398573
type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679398561 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679398561 :: a) = SubtractSym1 a6989586621679398561
type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679129674 :: k) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply (DefaultEqSym0 :: TyFun k (k ~> Bool) -> Type) (a6989586621679129674 :: k) = DefaultEqSym1 a6989586621679129674
type Apply ((<=?@#@$) :: TyFun k (k ~> Bool) -> Type) (a6989586621679370104 :: k) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((<=?@#@$) :: TyFun k (k ~> Bool) -> Type) (a6989586621679370104 :: k) = (<=?@#@$$) a6989586621679370104
type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (x :: k) # 
Instance details

Defined in Data.Singletons

type Apply (SameKindSym0 :: TyFun k (k ~> Constraint) -> Type) (x :: k) = SameKindSym1 x
type Apply (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) (a6989586621680354872 :: Natural) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ReplicateM_Sym0 :: TyFun Natural (m a ~> m ()) -> Type) (a6989586621680354872 :: Natural) = ReplicateM_Sym1 a6989586621680354872 :: TyFun (m a) (m ()) -> Type
type Apply (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) (a6989586621680354894 :: Natural) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) (a6989586621680354894 :: Natural) = ReplicateMSym1 a6989586621680354894 :: TyFun (m a) (m [a]) -> Type
type Apply ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) (a6989586621679253960 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) (a6989586621679253960 :: a) = (&@#@$$) a6989586621679253960 :: TyFun (a ~> b) b -> Type
type Apply (Bool_Sym1 a6989586621679122246 :: TyFun a (Bool ~> a) -> Type) (a6989586621679122247 :: a) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym1 a6989586621679122246 :: TyFun a (Bool ~> a) -> Type) (a6989586621679122247 :: a) = Bool_Sym2 a6989586621679122246 a6989586621679122247
type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679544349 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679544349 :: a) = LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type
type Apply (DeleteBySym1 a6989586621679544773 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544774 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym1 a6989586621679544773 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544774 :: a) = DeleteBySym2 a6989586621679544773 a6989586621679544774
type Apply (InsertBySym1 a6989586621679544731 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544732 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym1 a6989586621679544731 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679544732 :: a) = InsertBySym2 a6989586621679544731 a6989586621679544732
type Apply (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807410 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807410 :: a) = ShowsPrecSym2 a6989586621679807409 a6989586621679807410
type Apply (EnumFromThenToSym1 a6989586621679414073 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414074 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679414073 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414074 :: a) = EnumFromThenToSym2 a6989586621679414073 a6989586621679414074
type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680159057 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680159057 :: a) = ArgSym1 a6989586621680159057 :: TyFun b (Arg a b) -> Type
type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679050782 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679050782 :: a) = Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type
type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679154354 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679154354 :: a) = ConstSym1 a6989586621679154354 :: TyFun b a -> Type
type Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) (a6989586621679154272 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) (a6989586621679154272 :: a) = SeqSym1 a6989586621679154272 :: TyFun b b -> Type
type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621679900552 :: a) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Apply (AsProxyTypeOfSym0 :: TyFun a (proxy a ~> a) -> Type) (a6989586621679900552 :: a) = AsProxyTypeOfSym1 a6989586621679900552 :: TyFun (proxy a) a -> Type
type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922567 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922567 :: a) = ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type
type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922306 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922306 :: a) = NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type
type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679387993 :: b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679387993 :: b) = Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type
type Apply (IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type) (a6989586621679124437 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type) (a6989586621679124437 :: k) = IfSym2 a6989586621679124436 a6989586621679124437
type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679050813 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679050813 :: a) = Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type
type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679271232 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679271232 :: a) = (<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type
type Apply (ScanlSym1 a6989586621680287221 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287222 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym1 a6989586621680287221 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287222 :: b) = ScanlSym2 a6989586621680287221 a6989586621680287222
type Apply (ScanrSym1 a6989586621680287209 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287210 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym1 a6989586621680287209 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621680287210 :: b) = ScanrSym2 a6989586621680287209 a6989586621680287210
type Apply (ScanlSym1 a6989586621679545226 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545227 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym1 a6989586621679545226 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545227 :: b) = ScanlSym2 a6989586621679545226 a6989586621679545227
type Apply (ScanrSym1 a6989586621679545199 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545200 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym1 a6989586621679545199 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545200 :: b) = ScanrSym2 a6989586621679545199 a6989586621679545200
type Apply (ComparingSym1 a6989586621679189957 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679189958 :: b) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym1 a6989586621679189957 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679189958 :: b) = ComparingSym2 a6989586621679189957 a6989586621679189958
type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679050862 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679050862 :: a) = Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type
type Apply (CurrySym1 a6989586621679147661 :: TyFun a (b ~> c) -> Type) (a6989586621679147662 :: a) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym1 a6989586621679147661 :: TyFun a (b ~> c) -> Type) (a6989586621679147662 :: a) = CurrySym2 a6989586621679147661 a6989586621679147662
type Apply (FlipSym1 a6989586621679154327 :: TyFun b (a ~> c) -> Type) (a6989586621679154328 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679154327 :: TyFun b (a ~> c) -> Type) (a6989586621679154328 :: b) = FlipSym2 a6989586621679154327 a6989586621679154328
type Apply (Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679050814 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679050814 :: b) = Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type
type Apply (Foldl'Sym1 a6989586621679922542 :: TyFun b (t a ~> b) -> Type) (a6989586621679922543 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym1 a6989586621679922542 :: TyFun b (t a ~> b) -> Type) (a6989586621679922543 :: b) = Foldl'Sym2 a6989586621679922542 a6989586621679922543 :: TyFun (t a) b -> Type
type Apply (FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type) (a6989586621679922536 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type) (a6989586621679922536 :: b) = FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type
type Apply (Foldr'Sym1 a6989586621679922528 :: TyFun b (t a ~> b) -> Type) (a6989586621679922529 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym1 a6989586621679922528 :: TyFun b (t a ~> b) -> Type) (a6989586621679922529 :: b) = Foldr'Sym2 a6989586621679922528 a6989586621679922529 :: TyFun (t a) b -> Type
type Apply (FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type) (a6989586621679922522 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type) (a6989586621679922522 :: b) = FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type
type Apply (OnSym2 a6989586621679253973 a6989586621679253974 :: TyFun a (a ~> c) -> Type) (a6989586621679253975 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym2 a6989586621679253973 a6989586621679253974 :: TyFun a (a ~> c) -> Type) (a6989586621679253975 :: a) = OnSym3 a6989586621679253973 a6989586621679253974 a6989586621679253975
type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679050931 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679050931 :: a) = Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type
type Apply (MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103083 :: a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103083 :: a) = MapAccumLSym2 a6989586621680103082 a6989586621680103083 :: TyFun (t b) (a, t c) -> Type
type Apply (MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103073 :: a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680103073 :: a) = MapAccumRSym2 a6989586621680103072 a6989586621680103073 :: TyFun (t b) (a, t c) -> Type
type Apply (Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679050863 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679050863 :: b) = Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type
type Apply (FoldlMSym1 a6989586621679922477 :: TyFun b (t a ~> m b) -> Type) (a6989586621679922478 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym1 a6989586621679922477 :: TyFun b (t a ~> m b) -> Type) (a6989586621679922478 :: b) = FoldlMSym2 a6989586621679922477 a6989586621679922478 :: TyFun (t a) (m b) -> Type
type Apply (FoldrMSym1 a6989586621679922495 :: TyFun b (t a ~> m b) -> Type) (a6989586621679922496 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym1 a6989586621679922495 :: TyFun b (t a ~> m b) -> Type) (a6989586621679922496 :: b) = FoldrMSym2 a6989586621679922495 a6989586621679922496 :: TyFun (t a) (m b) -> Type
type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679051022 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679051022 :: a) = Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type
type Apply (Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679050932 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679050932 :: b) = Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type
type Apply (Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679050864 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679050864 :: c) = Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type
type Apply (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) (a6989586621679051137 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) (a6989586621679051137 :: a) = Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type
type Apply (Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679051023 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679051023 :: b) = Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type
type Apply (Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679050933 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679050933 :: c) = Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type
type Apply (Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679051138 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679051138 :: b) = Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type
type Apply (Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679051024 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679051024 :: c) = Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type
type Apply (Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679050934 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679050934 :: d) = Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type
type Apply (Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679051139 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679051139 :: c) = Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type
type Apply (Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679051025 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679051025 :: d) = Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type
type Apply (Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679051140 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679051140 :: d) = Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type
type Apply (Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679051026 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679051026 :: e) = Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type
type Apply (Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679051141 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679051141 :: e) = Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type
type Apply (Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679051142 :: f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679051142 :: f) = Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type
type Apply ((<**>@#@$$) a6989586621679271211 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679271212 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<**>@#@$$) a6989586621679271211 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679271212 :: f (a ~> b)) = a6989586621679271211 <**> a6989586621679271212
type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621680286938 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621680286938 :: NonEmpty a) = (!!@#@$$) a6989586621680286938
type Apply ((:$$:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621679803713 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply ((:$$:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621679803713 :: ErrorMessage' s) = (:$$:@#@$$) a6989586621679803713
type Apply ((:<>:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621679803710 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply ((:<>:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621679803710 :: ErrorMessage' s) = (:<>:@#@$$) a6989586621679803710
type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621680286965 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym0 :: TyFun [a] (NonEmpty a ~> Bool) -> Type) (a6989586621680286965 :: [a]) = IsPrefixOfSym1 a6989586621680286965
type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679544266 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679544266 :: [a]) = (!!@#@$$) a6989586621679544266
type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679545415 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntercalateSym0 :: TyFun [a] ([[a]] ~> [a]) -> Type) (a6989586621679545415 :: [a]) = IntercalateSym1 a6989586621679545415
type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679656297 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (StripPrefixSym0 :: TyFun [a] ([a] ~> Maybe [a]) -> Type) (a6989586621679656297 :: [a]) = StripPrefixSym1 a6989586621679656297
type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545011 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsInfixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545011 :: [a]) = IsInfixOfSym1 a6989586621679545011
type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545025 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsPrefixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545025 :: [a]) = IsPrefixOfSym1 a6989586621679545025
type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545018 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsSuffixOfSym0 :: TyFun [a] ([a] ~> Bool) -> Type) (a6989586621679545018 :: [a]) = IsSuffixOfSym1 a6989586621679545018
type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544612 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544612 :: [a]) = IntersectSym1 a6989586621679544612
type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544203 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionSym0 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544203 :: [a]) = UnionSym1 a6989586621679544203
type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544792 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((\\@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544792 :: [a]) = (\\@#@$$) a6989586621679544792
type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679154364 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679154364 :: [a]) = (++@#@$$) a6989586621679154364
type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807418 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807418 :: [a]) = ShowListSym1 a6989586621679807418
type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621680286929 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621680286929 :: NonEmpty a) = ZipSym1 a6989586621680286929 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type
type Apply (DeleteFirstsBySym1 a6989586621679544763 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544764 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym1 a6989586621679544763 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544764 :: [a]) = DeleteFirstsBySym2 a6989586621679544763 a6989586621679544764
type Apply (IntersectBySym1 a6989586621679544588 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544589 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym1 a6989586621679544588 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544589 :: [a]) = IntersectBySym2 a6989586621679544588 a6989586621679544589
type Apply (UnionBySym1 a6989586621679544211 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544212 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym1 a6989586621679544211 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679544212 :: [a]) = UnionBySym2 a6989586621679544211 a6989586621679544212
type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679544986 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679544986 :: [a]) = ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type
type Apply (ShowListWithSym1 a6989586621679807383 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807384 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym1 a6989586621679807383 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807384 :: [a]) = ShowListWithSym2 a6989586621679807383 a6989586621679807384
type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679271374 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679271374 :: f a) = (<|>@#@$$) a6989586621679271374
type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679271380 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679271380 :: m a) = MplusSym1 a6989586621679271380
type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679544974 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679544974 :: [a]) = Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type
type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679271255 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679271255 :: f (a ~> b)) = (<*>@#@$$) a6989586621679271255
type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679357509 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679357509 :: f a) = (<&>@#@$$) a6989586621679357509 :: TyFun (a ~> b) (f b) -> Type
type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679357502 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679357502 :: f a) = ($>@#@$$) a6989586621679357502 :: TyFun b (f b) -> Type
type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679271211 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679271211 :: f a) = (<**>@#@$$) a6989586621679271211 :: TyFun (f (a ~> b)) (f b) -> Type
type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679271272 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679271272 :: f a) = (<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type
type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679271267 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679271267 :: f a) = (*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type
type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679270990 :: m (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679270990 :: m (a ~> b)) = ApSym1 a6989586621679270990
type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679271335 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679271335 :: m a) = (>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type
type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621680264763 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621680264763 :: m a) = MzipSym1 a6989586621680264763 :: TyFun (m b) (m (a, b)) -> Type
type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679271340 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679271340 :: m a) = (>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type
type Apply (ZipWithSym1 a6989586621680286918 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621680286919 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym1 a6989586621680286918 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621680286919 :: NonEmpty a) = ZipWithSym2 a6989586621680286918 a6989586621680286919
type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679656286 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679656286 :: [a]) = Zip4Sym1 a6989586621679656286 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type
type Apply (ZipWithSym1 a6989586621679544962 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679544963 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym1 a6989586621679544962 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679544963 :: [a]) = ZipWithSym2 a6989586621679544962 a6989586621679544963
type Apply (Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679544975 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679544975 :: [b]) = Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type
type Apply (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) (a6989586621680392419 :: f a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Apply (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) (a6989586621680392419 :: f a) = PairSym1 a6989586621680392419 :: TyFun (g a) (Product f g a) -> Type
type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621679922460 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621679922460 :: t a) = For_Sym1 a6989586621679922460 :: TyFun (a ~> f b) (f ()) -> Type
type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680103106 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680103106 :: t a) = ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type
type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621679922440 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621679922440 :: t a) = ForM_Sym1 a6989586621679922440 :: TyFun (a ~> m b) (m ()) -> Type
type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680103095 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680103095 :: t a) = ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type
type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679656263 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679656263 :: [a]) = Zip5Sym1 a6989586621679656263 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type
type Apply (ZipWith3Sym1 a6989586621679544947 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679544948 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym1 a6989586621679544947 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679544948 :: [a]) = ZipWith3Sym2 a6989586621679544947 a6989586621679544948
type Apply (ZipWithM_Sym1 a6989586621680354943 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621680354944 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithM_Sym1 a6989586621680354943 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621680354944 :: [a]) = ZipWithM_Sym2 a6989586621680354943 a6989586621680354944
type Apply (ZipWithMSym1 a6989586621680354953 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621680354954 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithMSym1 a6989586621680354953 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621680354954 :: [a]) = ZipWithMSym2 a6989586621680354953 a6989586621680354954
type Apply (Zip4Sym1 a6989586621679656286 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679656287 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym1 a6989586621679656286 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679656287 :: [b]) = Zip4Sym2 a6989586621679656286 a6989586621679656287 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type
type Apply (LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679271262 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679271262 :: f a) = LiftA2Sym2 a6989586621679271261 a6989586621679271262
type Apply (MzipWithSym1 a6989586621680264769 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621680264770 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym1 a6989586621680264769 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621680264770 :: m a) = MzipWithSym2 a6989586621680264769 a6989586621680264770
type Apply (LiftM2Sym1 a6989586621679271130 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679271131 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM2Sym1 a6989586621679271130 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679271131 :: m a1) = LiftM2Sym2 a6989586621679271130 a6989586621679271131
type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679656235 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679656235 :: [a]) = Zip6Sym1 a6989586621679656235 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type
type Apply (ZipWith4Sym1 a6989586621679656166 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679656167 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym1 a6989586621679656166 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679656167 :: [a]) = ZipWith4Sym2 a6989586621679656166 a6989586621679656167
type Apply (Zip5Sym1 a6989586621679656263 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679656264 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym1 a6989586621679656263 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679656264 :: [b]) = Zip5Sym2 a6989586621679656263 a6989586621679656264 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type
type Apply (ZipWith3Sym2 a6989586621679544947 a6989586621679544948 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679544949 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym2 a6989586621679544947 a6989586621679544948 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679544949 :: [b]) = ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949
type Apply (Zip4Sym2 a6989586621679656286 a6989586621679656287 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679656288 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym2 a6989586621679656286 a6989586621679656287 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679656288 :: [c]) = Zip4Sym3 a6989586621679656286 a6989586621679656287 a6989586621679656288 :: TyFun [d] [(a, b, c, d)] -> Type
type Apply (LiftA3Sym1 a6989586621679271189 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679271190 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym1 a6989586621679271189 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679271190 :: f a) = LiftA3Sym2 a6989586621679271189 a6989586621679271190
type Apply (LiftM3Sym1 a6989586621679271100 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679271101 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym1 a6989586621679271100 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679271101 :: m a1) = LiftM3Sym2 a6989586621679271100 a6989586621679271101
type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679656202 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679656202 :: [a]) = Zip7Sym1 a6989586621679656202 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type
type Apply (ZipWith5Sym1 a6989586621679656143 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679656144 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym1 a6989586621679656143 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679656144 :: [a]) = ZipWith5Sym2 a6989586621679656143 a6989586621679656144
type Apply (Zip6Sym1 a6989586621679656235 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679656236 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym1 a6989586621679656235 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679656236 :: [b]) = Zip6Sym2 a6989586621679656235 a6989586621679656236 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type
type Apply (ZipWith4Sym2 a6989586621679656166 a6989586621679656167 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679656168 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym2 a6989586621679656166 a6989586621679656167 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679656168 :: [b]) = ZipWith4Sym3 a6989586621679656166 a6989586621679656167 a6989586621679656168
type Apply (Zip5Sym2 a6989586621679656263 a6989586621679656264 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679656265 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym2 a6989586621679656263 a6989586621679656264 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679656265 :: [c]) = Zip5Sym3 a6989586621679656263 a6989586621679656264 a6989586621679656265 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type
type Apply (LiftA3Sym2 a6989586621679271189 a6989586621679271190 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679271191 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym2 a6989586621679271189 a6989586621679271190 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679271191 :: f b) = LiftA3Sym3 a6989586621679271189 a6989586621679271190 a6989586621679271191
type Apply (LiftM4Sym1 a6989586621679271061 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679271062 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym1 a6989586621679271061 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679271062 :: m a1) = LiftM4Sym2 a6989586621679271061 a6989586621679271062
type Apply (LiftM3Sym2 a6989586621679271100 a6989586621679271101 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679271102 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym2 a6989586621679271100 a6989586621679271101 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679271102 :: m a2) = LiftM3Sym3 a6989586621679271100 a6989586621679271101 a6989586621679271102
type Apply (ZipWith6Sym1 a6989586621679656116 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679656117 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym1 a6989586621679656116 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679656117 :: [a]) = ZipWith6Sym2 a6989586621679656116 a6989586621679656117
type Apply (Zip7Sym1 a6989586621679656202 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679656203 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym1 a6989586621679656202 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679656203 :: [b]) = Zip7Sym2 a6989586621679656202 a6989586621679656203 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type
type Apply (ZipWith5Sym2 a6989586621679656143 a6989586621679656144 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679656145 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym2 a6989586621679656143 a6989586621679656144 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679656145 :: [b]) = ZipWith5Sym3 a6989586621679656143 a6989586621679656144 a6989586621679656145
type Apply (Zip6Sym2 a6989586621679656235 a6989586621679656236 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679656237 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym2 a6989586621679656235 a6989586621679656236 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679656237 :: [c]) = Zip6Sym3 a6989586621679656235 a6989586621679656236 a6989586621679656237 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type
type Apply (ZipWith4Sym3 a6989586621679656166 a6989586621679656167 a6989586621679656168 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679656169 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym3 a6989586621679656166 a6989586621679656167 a6989586621679656168 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679656169 :: [c]) = ZipWith4Sym4 a6989586621679656166 a6989586621679656167 a6989586621679656168 a6989586621679656169
type Apply (Zip5Sym3 a6989586621679656263 a6989586621679656264 a6989586621679656265 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679656266 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym3 a6989586621679656263 a6989586621679656264 a6989586621679656265 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679656266 :: [d]) = Zip5Sym4 a6989586621679656263 a6989586621679656264 a6989586621679656265 a6989586621679656266 :: TyFun [e] [(a, b, c, d, e)] -> Type
type Apply (LiftM5Sym1 a6989586621679271013 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679271014 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym1 a6989586621679271013 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679271014 :: m a1) = LiftM5Sym2 a6989586621679271013 a6989586621679271014
type Apply (LiftM4Sym2 a6989586621679271061 a6989586621679271062 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679271063 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym2 a6989586621679271061 a6989586621679271062 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679271063 :: m a2) = LiftM4Sym3 a6989586621679271061 a6989586621679271062 a6989586621679271063
type Apply (ZipWith7Sym1 a6989586621679656085 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679656086 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym1 a6989586621679656085 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679656086 :: [a]) = ZipWith7Sym2 a6989586621679656085 a6989586621679656086
type Apply (ZipWith6Sym2 a6989586621679656116 a6989586621679656117 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679656118 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym2 a6989586621679656116 a6989586621679656117 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679656118 :: [b]) = ZipWith6Sym3 a6989586621679656116 a6989586621679656117 a6989586621679656118
type Apply (Zip7Sym2 a6989586621679656202 a6989586621679656203 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679656204 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym2 a6989586621679656202 a6989586621679656203 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679656204 :: [c]) = Zip7Sym3 a6989586621679656202 a6989586621679656203 a6989586621679656204 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type
type Apply (ZipWith5Sym3 a6989586621679656143 a6989586621679656144 a6989586621679656145 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679656146 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym3 a6989586621679656143 a6989586621679656144 a6989586621679656145 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679656146 :: [c]) = ZipWith5Sym4 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146
type Apply (Zip6Sym3 a6989586621679656235 a6989586621679656236 a6989586621679656237 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679656238 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym3 a6989586621679656235 a6989586621679656236 a6989586621679656237 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679656238 :: [d]) = Zip6Sym4 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type
type Apply (LiftM5Sym2 a6989586621679271013 a6989586621679271014 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679271015 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym2 a6989586621679271013 a6989586621679271014 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679271015 :: m a2) = LiftM5Sym3 a6989586621679271013 a6989586621679271014 a6989586621679271015
type Apply (LiftM4Sym3 a6989586621679271061 a6989586621679271062 a6989586621679271063 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679271064 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym3 a6989586621679271061 a6989586621679271062 a6989586621679271063 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679271064 :: m a3) = LiftM4Sym4 a6989586621679271061 a6989586621679271062 a6989586621679271063 a6989586621679271064
type Apply (ZipWith7Sym2 a6989586621679656085 a6989586621679656086 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679656087 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym2 a6989586621679656085 a6989586621679656086 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679656087 :: [b]) = ZipWith7Sym3 a6989586621679656085 a6989586621679656086 a6989586621679656087
type Apply (ZipWith6Sym3 a6989586621679656116 a6989586621679656117 a6989586621679656118 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679656119 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym3 a6989586621679656116 a6989586621679656117 a6989586621679656118 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679656119 :: [c]) = ZipWith6Sym4 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119
type Apply (Zip7Sym3 a6989586621679656202 a6989586621679656203 a6989586621679656204 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679656205 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym3 a6989586621679656202 a6989586621679656203 a6989586621679656204 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679656205 :: [d]) = Zip7Sym4 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type
type Apply (ZipWith5Sym4 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679656147 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym4 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679656147 :: [d]) = ZipWith5Sym5 a6989586621679656143 a6989586621679656144 a6989586621679656145 a6989586621679656146 a6989586621679656147
type Apply (Zip6Sym4 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679656239 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym4 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679656239 :: [e]) = Zip6Sym5 a6989586621679656235 a6989586621679656236 a6989586621679656237 a6989586621679656238 a6989586621679656239 :: TyFun [f] [(a, b, c, d, e, f)] -> Type
type Apply (LiftM5Sym3 a6989586621679271013 a6989586621679271014 a6989586621679271015 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679271016 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym3 a6989586621679271013 a6989586621679271014 a6989586621679271015 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679271016 :: m a3) = LiftM5Sym4 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016
type Apply (ZipWith7Sym3 a6989586621679656085 a6989586621679656086 a6989586621679656087 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679656088 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym3 a6989586621679656085 a6989586621679656086 a6989586621679656087 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679656088 :: [c]) = ZipWith7Sym4 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088
type Apply (ZipWith6Sym4 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679656120 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym4 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679656120 :: [d]) = ZipWith6Sym5 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120
type Apply (Zip7Sym4 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679656206 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym4 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679656206 :: [e]) = Zip7Sym5 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type
type Apply (LiftM5Sym4 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679271017 :: m a4) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym4 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679271017 :: m a4) = LiftM5Sym5 a6989586621679271013 a6989586621679271014 a6989586621679271015 a6989586621679271016 a6989586621679271017
type Apply (ZipWith7Sym4 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679656089 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym4 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679656089 :: [d]) = ZipWith7Sym5 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089
type Apply (ZipWith6Sym5 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679656121 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym5 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679656121 :: [e]) = ZipWith6Sym6 a6989586621679656116 a6989586621679656117 a6989586621679656118 a6989586621679656119 a6989586621679656120 a6989586621679656121
type Apply (Zip7Sym5 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679656207 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym5 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679656207 :: [f]) = Zip7Sym6 a6989586621679656202 a6989586621679656203 a6989586621679656204 a6989586621679656205 a6989586621679656206 a6989586621679656207 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type
type Apply (ZipWith7Sym5 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679656090 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym5 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679656090 :: [e]) = ZipWith7Sym6 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090
type Apply (ZipWith7Sym6 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679656091 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym6 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679656091 :: [f]) = ZipWith7Sym7 a6989586621679656085 a6989586621679656086 a6989586621679656087 a6989586621679656088 a6989586621679656089 a6989586621679656090 a6989586621679656091
type Demote (k1 ~> k2) # 
Instance details

Defined in Data.Singletons

type Demote (k1 ~> k2) = Demote k1 -> Demote k2
type Sing # 
Instance details

Defined in Data.Singletons

type Sing = SLambda :: (k1 ~> k2) -> Type
type Mempty Source # 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
type Mconcat (arg :: [a ~> b]) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (arg :: [a ~> b])
type Sconcat (arg :: NonEmpty (a ~> b)) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Sconcat (arg :: NonEmpty (a ~> b))
type Mappend (arg1 :: a ~> b) (arg2 :: a ~> b) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: a ~> b) (arg2 :: a ~> b)
type (a2 :: a1 ~> b) <> (a3 :: a1 ~> b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type (a2 :: a1 ~> b) <> (a3 :: a1 ~> b)
type Apply ((&@#@$$) a6989586621679253960 :: TyFun (a ~> b) b -> Type) (a6989586621679253961 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply ((&@#@$$) a6989586621679253960 :: TyFun (a ~> b) b -> Type) (a6989586621679253961 :: a ~> b) = a6989586621679253960 & a6989586621679253961
type Apply ((<&>@#@$$) a6989586621679357509 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679357510 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$$) a6989586621679357509 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679357510 :: a ~> b) = a6989586621679357509 <&> a6989586621679357510
type Apply ((>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679271336 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679271336 :: a ~> m b) = a6989586621679271335 >>= a6989586621679271336
type Apply (For_Sym1 a6989586621679922460 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621679922461 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym1 a6989586621679922460 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621679922461 :: a ~> f b) = For_ a6989586621679922460 a6989586621679922461
type Apply (ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680103107 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForSym1 a6989586621680103106 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680103107 :: a ~> f b) = For a6989586621680103106 a6989586621680103107
type Apply (ForM_Sym1 a6989586621679922440 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621679922441 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym1 a6989586621679922440 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621679922441 :: a ~> m b) = ForM_ a6989586621679922440 a6989586621679922441
type Apply (ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680103096 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForMSym1 a6989586621680103095 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680103096 :: a ~> m b) = ForM a6989586621680103095 a6989586621680103096
type Apply (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621679807347 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621679807347 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621679807346 a6989586621679807347
type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807383 :: a ~> (Symbol ~> Symbol)) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807383 :: a ~> (Symbol ~> Symbol)) = ShowListWithSym1 a6989586621679807383
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286856 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286856 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621680286856
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679544751 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679544751 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621679544751
type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679544731 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679544731 :: a ~> (a ~> Ordering)) = InsertBySym1 a6989586621679544731
type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286992 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286992 :: a ~> (a ~> Bool)) = GroupBy1Sym1 a6989586621680286992
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286869 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286869 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621680286869
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544763 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544763 :: a ~> (a ~> Bool)) = DeleteFirstsBySym1 a6989586621679544763
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544588 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544588 :: a ~> (a ~> Bool)) = IntersectBySym1 a6989586621679544588
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544211 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679544211 :: a ~> (a ~> Bool)) = UnionBySym1 a6989586621679544211
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287048 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287048 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621680287048
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679544364 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679544364 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621679544364
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679544231 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679544231 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621679544231
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679544773 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679544773 :: a ~> (a ~> Bool)) = DeleteBySym1 a6989586621679544773
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287198 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287198 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621680287198
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287190 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680287190 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621680287190
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545217 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545217 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679545217
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545179 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545179 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679545179
type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679545295 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679545295 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679545295
type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287110 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287110 :: a ~> Bool) = BreakSym1 a6989586621680287110
type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287092 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287092 :: a ~> Bool) = PartitionSym1 a6989586621680287092
type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287119 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621680287119 :: a ~> Bool) = SpanSym1 a6989586621680287119
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287128 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287128 :: a ~> Bool) = DropWhileSym1 a6989586621680287128
type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287101 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287101 :: a ~> Bool) = FilterSym1 a6989586621680287101
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287137 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621680287137 :: a ~> Bool) = TakeWhileSym1 a6989586621680287137
type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679154281 :: a ~> Bool) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679154281 :: a ~> Bool) = UntilSym1 a6989586621679154281
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679544640 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679544640 :: a ~> Bool) = FindIndexSym1 a6989586621679544640
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544458 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544458 :: a ~> Bool) = BreakSym1 a6989586621679544458
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544342 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544342 :: a ~> Bool) = PartitionSym1 a6989586621679544342
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544497 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544497 :: a ~> Bool) = SpanSym1 a6989586621679544497
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679544619 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679544619 :: a ~> Bool) = FindIndicesSym1 a6989586621679544619
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544538 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544538 :: a ~> Bool) = DropWhileEndSym1 a6989586621679544538
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544559 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544559 :: a ~> Bool) = DropWhileSym1 a6989586621679544559
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544674 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544674 :: a ~> Bool) = FilterSym1 a6989586621679544674
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544574 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544574 :: a ~> Bool) = TakeWhileSym1 a6989586621679544574
type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621679922335 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621679922335 :: a ~> (a ~> Ordering)) = MaximumBySym1 a6989586621679922335 :: TyFun (t a) a -> Type
type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621679922315 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621679922315 :: a ~> (a ~> Ordering)) = MinimumBySym1 a6989586621679922315 :: TyFun (t a) a -> Type
type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922553 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922553 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type
type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922548 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922548 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287209 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287209 :: a ~> (b ~> b)) = ScanrSym1 a6989586621680287209
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545199 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545199 :: a ~> (b ~> b)) = ScanrSym1 a6989586621679545199
type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679390184 :: a ~> Maybe b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679390184 :: a ~> Maybe b) = MapMaybeSym1 a6989586621679390184
type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287356 :: a ~> (b, Maybe a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287356 :: a ~> (b, Maybe a)) = UnfoldSym1 a6989586621680287356
type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287321 :: a ~> (b, Maybe a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621680287321 :: a ~> (b, Maybe a)) = UnfoldrSym1 a6989586621680287321
type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621680354827 :: a ~> Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621680354827 :: a ~> Bool) = MfilterSym1 a6989586621680354827 :: TyFun (m a) (m a) -> Type
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621679922286 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621679922286 :: a ~> Bool) = FindSym1 a6989586621679922286 :: TyFun (t a) (Maybe a) -> Type
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922355 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922355 :: a ~> Bool) = AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922364 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922364 :: a ~> Bool) = AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type
type Apply (UntilSym1 a6989586621679154281 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679154282 :: a ~> a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym1 a6989586621679154281 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679154282 :: a ~> a) = UntilSym2 a6989586621679154281 a6989586621679154282
type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286976 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286976 :: a ~> b) = GroupAllWith1Sym1 a6989586621680286976
type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286985 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621680286985 :: a ~> b) = GroupWith1Sym1 a6989586621680286985
type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621680287251 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621680287251 :: a ~> b) = MapSym1 a6989586621680287251
type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287030 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287030 :: a ~> b) = GroupAllWithSym1 a6989586621680287030
type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287039 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621680287039 :: a ~> b) = GroupWithSym1 a6989586621680287039
type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679154373 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679154373 :: a ~> b) = MapSym1 a6989586621679154373
type Apply ((@@@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) # 
Instance details

Defined in Data.Singletons

type Apply ((@@@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) = (@@@#@$$) f
type Apply (ApplySym0 :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) # 
Instance details

Defined in Data.Singletons

type Apply (ApplySym0 :: TyFun (a ~> b) (a ~> b) -> Type) (f :: a ~> b) = ApplySym1 f
type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154299 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154299 :: a ~> b) = ($!@#@$$) a6989586621679154299
type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154308 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154308 :: a ~> b) = ($@#@$$) a6989586621679154308
type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621680355005 :: a ~> m Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621680355005 :: a ~> m Bool) = FilterMSym1 a6989586621680355005
type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286847 :: a ~> o) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621680286847 :: a ~> o) = SortWithSym1 a6989586621680286847
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287221 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621680287221 :: b ~> (a ~> b)) = ScanlSym1 a6989586621680287221
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545226 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545226 :: b ~> (a ~> b)) = ScanlSym1 a6989586621679545226
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679545055 :: b ~> Maybe (a, b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679545055 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679545055
type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679189957 :: b ~> a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679189957 :: b ~> a) = ComparingSym1 a6989586621679189957
type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679147661 :: (a, b) ~> c) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679147661 :: (a, b) ~> c) = CurrySym1 a6989586621679147661
type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922528 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922528 :: a ~> (b ~> b)) = Foldr'Sym1 a6989586621679922528 :: TyFun b (t a ~> b) -> Type
type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922521 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922521 :: a ~> (b ~> b)) = FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621680286918 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621680286918 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621680286918
type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679147653 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679147653 :: a ~> (b ~> c)) = UncurrySym1 a6989586621679147653
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679544962 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679544962 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621679544962
type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679154327 :: a ~> (b ~> c)) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679154327 :: a ~> (b ~> c)) = FlipSym1 a6989586621679154327
type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621679922383 :: a ~> [b]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621679922383 :: a ~> [b]) = ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type
type Apply (Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679387994 :: a ~> b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679387994 :: a ~> b) = Maybe_Sym2 a6989586621679387993 a6989586621679387994
type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271227 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271227 :: a ~> b) = FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type
type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271200 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271200 :: a ~> b) = LiftASym1 a6989586621679271200 :: TyFun (f a) (f b) -> Type
type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679357520 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679357520 :: a ~> b) = (<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type
type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621680354845 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621680354845 :: a ~> b) = (<$!>@#@$$) a6989586621680354845 :: TyFun (m a) (m b) -> Type
type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680103058 :: a ~> b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680103058 :: a ~> b) = FmapDefaultSym1 a6989586621680103058 :: TyFun (t a) (t b) -> Type
type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679259290 :: a ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679259290 :: a ~> c) = Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type
type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621679922515 :: a ~> m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621679922515 :: a ~> m) = FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type
type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680103039 :: a ~> m) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680103039 :: a ~> m) = FoldMapDefaultSym1 a6989586621680103039 :: TyFun (t a) m -> Type
type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679271176 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679271176 :: a ~> m b) = (=<<@#@$$) a6989586621679271176
type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679271151 :: a1 ~> r) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679271151 :: a1 ~> r) = LiftMSym1 a6989586621679271151 :: TyFun (m a1) (m r) -> Type
type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922542 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922542 :: b ~> (a ~> b)) = Foldl'Sym1 a6989586621679922542 :: TyFun b (t a ~> b) -> Type
type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922535 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922535 :: b ~> (a ~> b)) = FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type
type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679253973 :: b ~> (b ~> c)) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679253973 :: b ~> (b ~> c)) = OnSym1 a6989586621679253973 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type
type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679154339 :: b ~> c) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679154339 :: b ~> c) = (.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type
type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679544947 :: a ~> (b ~> (c ~> d))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679544947 :: a ~> (b ~> (c ~> d))) = ZipWith3Sym1 a6989586621679544947
type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103082 :: a ~> (b ~> (a, c))) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103082 :: a ~> (b ~> (a, c))) = MapAccumLSym1 a6989586621680103082 :: TyFun a (t b ~> (a, t c)) -> Type
type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103072 :: a ~> (b ~> (a, c))) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680103072 :: a ~> (b ~> (a, c))) = MapAccumRSym1 a6989586621680103072 :: TyFun a (t b ~> (a, t c)) -> Type
type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679271261 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679271261 :: a ~> (b ~> c)) = LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type
type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621680264769 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621680264769 :: a ~> (b ~> c)) = MzipWithSym1 a6989586621680264769 :: TyFun (m a) (m b ~> m c) -> Type
type Apply (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621679922495 :: a ~> (b ~> m b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621679922495 :: a ~> (b ~> m b)) = FoldrMSym1 a6989586621679922495 :: TyFun b (t a ~> m b) -> Type
type Apply (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) (a6989586621680354943 :: a ~> (b ~> m c)) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) (a6989586621680354943 :: a ~> (b ~> m c)) = ZipWithM_Sym1 a6989586621680354943
type Apply (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) (a6989586621680354953 :: a ~> (b ~> m c)) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) (a6989586621680354953 :: a ~> (b ~> m c)) = ZipWithMSym1 a6989586621680354953
type Apply (OnSym1 a6989586621679253973 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679253974 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym1 a6989586621679253973 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679253974 :: a ~> b) = OnSym2 a6989586621679253973 a6989586621679253974
type Apply ((.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679154340 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679154340 :: a ~> b) = a6989586621679154339 .@#@$$$ a6989586621679154340
type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621679922469 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621679922469 :: a ~> f b) = Traverse_Sym1 a6989586621679922469 :: TyFun (t a) (f ()) -> Type
type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680096860 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680096860 :: a ~> f b) = TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type
type Apply (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) (a6989586621680354962 :: a ~> m (b, c)) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) (a6989586621680354962 :: a ~> m (b, c)) = MapAndUnzipMSym1 a6989586621680354962
type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621680354988 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621680354988 :: a ~> m b) = (>=>@#@$$) a6989586621680354988 :: TyFun (b ~> m c) (a ~> m c) -> Type
type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621679922449 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621679922449 :: a ~> m b) = MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type
type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680096868 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680096868 :: a ~> m b) = MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type
type Apply (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) (a6989586621679271130 :: a1 ~> (a2 ~> r)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) (a6989586621679271130 :: a1 ~> (a2 ~> r)) = LiftM2Sym1 a6989586621679271130 :: TyFun (m a1) (m a2 ~> m r) -> Type
type Apply (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621679922477 :: b ~> (a ~> m b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621679922477 :: b ~> (a ~> m b)) = FoldlMSym1 a6989586621679922477 :: TyFun b (t a ~> m b) -> Type
type Apply (Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679259291 :: b ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679259291 :: b ~> c) = Either_Sym2 a6989586621679259290 a6989586621679259291
type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621680354976 :: b ~> m c) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621680354976 :: b ~> m c) = (<=<@#@$$) a6989586621680354976 :: TyFun (a ~> m b) (a ~> m c) -> Type
type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679656166 :: a ~> (b ~> (c ~> (d ~> e)))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679656166 :: a ~> (b ~> (c ~> (d ~> e)))) = ZipWith4Sym1 a6989586621679656166
type Apply (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) (a6989586621679271189 :: a ~> (b ~> (c ~> d))) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) (a6989586621679271189 :: a ~> (b ~> (c ~> d))) = LiftA3Sym1 a6989586621679271189 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type
type Apply ((<=<@#@$$) a6989586621680354976 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621680354977 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<=<@#@$$) a6989586621680354976 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621680354977 :: a ~> m b) = a6989586621680354976 <=<@#@$$$ a6989586621680354977
type Apply (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) (a6989586621679271100 :: a1 ~> (a2 ~> (a3 ~> r))) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) (a6989586621679271100 :: a1 ~> (a2 ~> (a3 ~> r))) = LiftM3Sym1 a6989586621679271100 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type
type Apply ((>=>@#@$$) a6989586621680354988 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621680354989 :: b ~> m c) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((>=>@#@$$) a6989586621680354988 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621680354989 :: b ~> m c) = a6989586621680354988 >=>@#@$$$ a6989586621680354989
type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679656143 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679656143 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) = ZipWith5Sym1 a6989586621679656143
type Apply (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) (a6989586621679271061 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) (a6989586621679271061 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) = LiftM4Sym1 a6989586621679271061 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type
type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621679656116 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))))) -> Type) (a6989586621679656116 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) = ZipWith6Sym1 a6989586621679656116
type Apply (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) (a6989586621679271013 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) (a6989586621679271013 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) = LiftM5Sym1 a6989586621679271013 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type
type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621679656085 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))))) -> Type) (a6989586621679656085 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) = ZipWith7Sym1 a6989586621679656085

type family UnwrapSing (ws :: WrappedSing a) :: Sing a where ... #

Equations

UnwrapSing ('WrapSing s :: WrappedSing a) = s 

newtype WrappedSing (a :: k) where #

Constructors

WrapSing 

Fields

Instances

Instances details
SingKind (WrappedSing a) # 
Instance details

Defined in Data.Singletons

Associated Types

type Demote (WrappedSing a) 
Instance details

Defined in Data.Singletons

Methods

fromSing :: forall (a0 :: WrappedSing a). Sing a0 -> Demote (WrappedSing a) #

toSing :: Demote (WrappedSing a) -> SomeSing (WrappedSing a) #

SingI a => SingI ('WrapSing s :: WrappedSing a) # 
Instance details

Defined in Data.Singletons

Methods

sing :: Sing ('WrapSing s :: WrappedSing a) #

type Demote (WrappedSing a) # 
Instance details

Defined in Data.Singletons

type Sing # 
Instance details

Defined in Data.Singletons

type (~>) a b = TyFun a b -> Type #

data (~>@#@$) (a :: TyFun Type (Type ~> Type)) #

Instances

Instances details
type Apply (~>@#@$) (x :: Type) # 
Instance details

Defined in Data.Singletons

type Apply (~>@#@$) (x :: Type) = (~>@#@$$) x

data a ~>@#@$$ (b :: TyFun Type Type) #

Instances

Instances details
type Apply ((~>@#@$$) x :: TyFun Type Type -> Type) (y :: Type) # 
Instance details

Defined in Data.Singletons

type Apply ((~>@#@$$) x :: TyFun Type Type -> Type) (y :: Type) = x ~> y

type (~>@#@$$$) x y = x ~> y #

Promoted and singled types, classes, and related functions

Basic data types

data SBool (a :: Bool) where Source #

Constructors

SFalse :: SBool 'False 
STrue :: SBool 'True 

Instances

Instances details
TestCoercion SBool Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a :: Bool) (b :: Bool). SBool a -> SBool b -> Maybe (Coercion a b) #

TestEquality SBool Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a :: Bool) (b :: Bool). SBool a -> SBool b -> Maybe (a :~: b) #

Show (SBool z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SBool z -> ShowS #

show :: SBool z -> String #

showList :: [SBool z] -> ShowS #

Eq (SBool z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: SBool z -> SBool z -> Bool #

(/=) :: SBool z -> SBool z -> Bool #

type family If (cond :: Bool) (tru :: k) (fls :: k) :: k where ... #

Type-level If. If True a b ==> a; If False a b ==> b

Equations

If 'True (tru :: k) (fls :: k) = tru 
If 'False (tru :: k) (fls :: k) = fls 

sIf :: forall {k} (a :: Bool) (b :: k) (c :: k). Sing a -> Sing b -> Sing c -> Sing (If a b c) Source #

Conditional over singletons

type family (a :: Bool) && (b :: Bool) :: Bool where ... infixr 3 #

Type-level "and"

Equations

'False && a = 'False 
'True && a = a 
a && 'False = 'False 
a && 'True = a 
a && a = a 

(%&&) :: forall (a :: Bool) (b :: Bool). Sing a -> Sing b -> Sing (a && b) infixr 3 Source #

Conjunction of singletons

type family (a :: Bool) || (b :: Bool) :: Bool where ... infixr 2 #

Type-level "or"

Equations

'False || a = a 
'True || a = 'True 
a || 'False = a 
a || 'True = 'True 
a || a = a 

(%||) :: forall (a :: Bool) (b :: Bool). Sing a -> Sing b -> Sing (a || b) infixr 2 Source #

Disjunction of singletons

type family Not (a :: Bool) = (res :: Bool) | res -> a where ... #

Type-level "not". An injective type family since 4.10.0.0.

Since: base-4.7.0.0

Equations

Not 'False = 'True 
Not 'True = 'False 

sNot :: forall (a :: Bool). Sing a -> Sing (Not a) Source #

Negation of a singleton

type family Otherwise :: Bool where ... Source #

Equations

Otherwise = TrueSym0 

data SMaybe (a1 :: Maybe a) where Source #

Constructors

SNothing :: forall a. SMaybe ('Nothing :: Maybe a) 
SJust :: forall a (n :: a). Sing n -> SMaybe ('Just n) 

Instances

Instances details
SDecide a => TestCoercion (SMaybe :: Maybe a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: Maybe a) (b :: Maybe a). SMaybe a0 -> SMaybe b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SMaybe :: Maybe a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: Maybe a) (b :: Maybe a). SMaybe a0 -> SMaybe b -> Maybe (a0 :~: b) #

ShowSing a => Show (SMaybe z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SMaybe z -> ShowS #

show :: SMaybe z -> String #

showList :: [SMaybe z] -> ShowS #

Eq (SMaybe z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: SMaybe z -> SMaybe z -> Bool #

(/=) :: SMaybe z -> SMaybe z -> Bool #

maybe_ is a reimplementation of the maybe function with a different name to avoid clashing with the Maybe data type when promoted.

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

type family Maybe_ (a1 :: b) (a2 :: a ~> b) (a3 :: Maybe a) :: b where ... Source #

Equations

Maybe_ (n :: b) (_1 :: a ~> b) ('Nothing :: Maybe a) = n 
Maybe_ (_1 :: k2) (f :: k1 ~> k2) ('Just x :: Maybe k1) = Apply f x 

sMaybe_ :: forall b a (t1 :: b) (t2 :: a ~> b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Maybe_ t1 t2 t3) Source #

data SEither (a1 :: Either a b) where Source #

Constructors

SLeft :: forall a b (n :: a). Sing n -> SEither ('Left n :: Either a b) 
SRight :: forall a b (n :: b). Sing n -> SEither ('Right n :: Either a b) 

Instances

Instances details
(SDecide a, SDecide b) => TestCoercion (SEither :: Either a b -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: Either a b) (b0 :: Either a b). SEither a0 -> SEither b0 -> Maybe (Coercion a0 b0) #

(SDecide a, SDecide b) => TestEquality (SEither :: Either a b -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: Either a b) (b0 :: Either a b). SEither a0 -> SEither b0 -> Maybe (a0 :~: b0) #

(ShowSing a, ShowSing b) => Show (SEither z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SEither z -> ShowS #

show :: SEither z -> String #

showList :: [SEither z] -> ShowS #

Eq (SEither z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: SEither z -> SEither z -> Bool #

(/=) :: SEither z -> SEither z -> Bool #

either_ is a reimplementation of the either function with a different name to avoid clashing with the Either data type when promoted.

either_ :: (a -> c) -> (b -> c) -> Either a b -> c Source #

type family Either_ (a1 :: a ~> c) (a2 :: b ~> c) (a3 :: Either a b) :: c where ... Source #

Equations

Either_ (f :: k1 ~> k2) (_1 :: b ~> k2) ('Left x :: Either k1 b) = Apply f x 
Either_ (_1 :: a ~> k2) (g :: k1 ~> k2) ('Right y :: Either a k1) = Apply g y 

sEither_ :: forall a c b (t1 :: a ~> c) (t2 :: b ~> c) (t3 :: Either a b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Either_ t1 t2 t3) Source #

data SOrdering (a :: Ordering) where Source #

Constructors

SLT :: SOrdering 'LT 
SEQ :: SOrdering 'EQ 
SGT :: SOrdering 'GT 

Instances

Instances details
TestCoercion SOrdering Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a :: Ordering) (b :: Ordering). SOrdering a -> SOrdering b -> Maybe (Coercion a b) #

TestEquality SOrdering Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a :: Ordering) (b :: Ordering). SOrdering a -> SOrdering b -> Maybe (a :~: b) #

Show (SOrdering z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Eq (SOrdering z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: SOrdering z -> SOrdering z -> Bool #

(/=) :: SOrdering z -> SOrdering z -> Bool #

data SChar (s :: Char) #

A value-level witness for a type-level character. This is commonly referred to as a singleton type, as for each c, there is a single value that inhabits the type SChar c (aside from bottom).

The definition of SChar is intentionally left abstract. To obtain an SChar value, use one of the following:

  1. The charSing method of KnownChar.
  2. The SChar pattern synonym.
  3. The withSomeSChar function, which creates an SChar from a Char.

Since: base-4.18.0.0

Instances

Instances details
TestCoercion SChar #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testCoercion :: forall (a :: Char) (b :: Char). SChar a -> SChar b -> Maybe (Coercion a b) #

TestEquality SChar #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testEquality :: forall (a :: Char) (b :: Char). SChar a -> SChar b -> Maybe (a :~: b) #

Show (SChar c) #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

showsPrec :: Int -> SChar c -> ShowS #

show :: SChar c -> String #

showList :: [SChar c] -> ShowS #

Eq (SChar c) #

Since: base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

(==) :: SChar c -> SChar c -> Bool #

(/=) :: SChar c -> SChar c -> Bool #

Ord (SChar c) #

Since: base-4.19.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

compare :: SChar c -> SChar c -> Ordering #

(<) :: SChar c -> SChar c -> Bool #

(<=) :: SChar c -> SChar c -> Bool #

(>) :: SChar c -> SChar c -> Bool #

(>=) :: SChar c -> SChar c -> Bool #

max :: SChar c -> SChar c -> SChar c #

min :: SChar c -> SChar c -> SChar c #

data Symbol #

(Kind) This is the kind of type-level symbols.

Instances

Instances details
Monoid Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Semigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons

IsString Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

fromString :: String -> Symbol #

SingKind Symbol

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Associated Types

type DemoteRep Symbol 
Instance details

Defined in GHC.Internal.Generics

type DemoteRep Symbol = String

Methods

fromSing :: forall (a :: Symbol). Sing a -> DemoteRep Symbol

Show Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Eq Symbol Source #

This bogus instance is helpful for people who want to define functions over Symbols that will only be used at the type level or as singletons.

Instance details

Defined in GHC.TypeLits.Singletons

Methods

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

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

Ord Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingKind PErrorMessage Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Associated Types

type Demote PErrorMessage 
Instance details

Defined in Data.Singletons.Base.TypeError

SingKind Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type Demote Symbol 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

fromSing :: forall (a :: Symbol). Sing a -> Demote Symbol #

toSing :: Demote Symbol -> SomeSing Symbol #

SDecide Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

(%~) :: forall (a :: Symbol) (b :: Symbol). Sing a -> Sing b -> Decision (a :~: b) #

PEq Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type (x :: Symbol) == (y :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (x :: Symbol) == (y :: Symbol) = DefaultEq x y
type (arg :: Symbol) /= (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) /= (arg1 :: Symbol)
SEq Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

(%==) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

PMonoid Symbol Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
type Mappend (arg1 :: Symbol) (arg2 :: Symbol) 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: Symbol) (arg2 :: Symbol)
type Mconcat (arg :: [Symbol]) 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (arg :: [Symbol])
SMonoid Symbol Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Symbol) Source #

sMappend :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Symbol]). Sing t -> Sing (Mconcat t) Source #

POrd Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type Compare (a :: Symbol) (b :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Compare (a :: Symbol) (b :: Symbol) = CmpSymbol a b
type (arg :: Symbol) < (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) < (arg1 :: Symbol)
type (arg :: Symbol) <= (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) <= (arg1 :: Symbol)
type (arg :: Symbol) > (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) > (arg1 :: Symbol)
type (arg :: Symbol) >= (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) >= (arg1 :: Symbol)
type Max (arg :: Symbol) (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Max (arg :: Symbol) (arg1 :: Symbol)
type Min (arg :: Symbol) (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Min (arg :: Symbol) (arg1 :: Symbol)
SOrd Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sCompare :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

PSemigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type (a :: Symbol) <> (b :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (a :: Symbol) <> (b :: Symbol) = AppendSymbol a b
type Sconcat (arg :: NonEmpty Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sconcat (arg :: NonEmpty Symbol)
SSemigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

(%<>) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty Symbol). Sing t -> Sing (Sconcat t) Source #

PIsString Symbol Source # 
Instance details

Defined in Data.String.Singletons

Associated Types

type FromString a 
Instance details

Defined in Data.String.Singletons

type FromString a = a
SIsString Symbol Source # 
Instance details

Defined in Data.String.Singletons

Methods

sFromString :: forall (t :: Symbol). Sing t -> Sing (FromString t :: Symbol) Source #

PShow Symbol Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec _1 (s :: Symbol) x 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec _1 (s :: Symbol) x
type Show_ (arg :: Symbol) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Symbol)
type ShowList (arg1 :: [Symbol]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Symbol]) arg2
SShow Symbol Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Symbol) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Symbol). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Symbol]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

TestCoercion SSymbol #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testCoercion :: forall (a :: Symbol) (b :: Symbol). SSymbol a -> SSymbol b -> Maybe (Coercion a b) #

TestEquality SSymbol #

Since: base-4.18.0.0

Instance details

Defined in GHC.Internal.TypeLits

Methods

testEquality :: forall (a :: Symbol) (b :: Symbol). SSymbol a -> SSymbol b -> Maybe (a :~: b) #

KnownSymbol a => SingI (a :: Symbol)

Since: base-4.9.0.0

Instance details

Defined in GHC.Internal.Generics

Methods

sing :: Sing a

KnownSymbol n => SingI (n :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing n #

SingI2 ('(:$$:) :: ErrorMessage' Symbol -> ErrorMessage' Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing2 :: forall (x :: PErrorMessage) (y :: PErrorMessage). Sing x -> Sing y -> Sing (x ':$$: y) #

SingI2 ('(:<>:) :: ErrorMessage' Symbol -> ErrorMessage' Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing2 :: forall (x :: PErrorMessage) (y :: PErrorMessage). Sing x -> Sing y -> Sing (x ':<>: y) #

SingI1 ('Text :: Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: Symbol). Sing x -> Sing ('Text x) #

SingI e1 => SingI1 ('(:$$:) e1 :: ErrorMessage' Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing (e1 ':$$: x) #

SingI e1 => SingI1 ('(:<>:) e1 :: ErrorMessage' Symbol -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing (e1 ':<>: x) #

SingI1 ('ShowType :: t -> ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: t). Sing x -> Sing ('ShowType x :: ErrorMessage' Symbol) #

SShow a => SingI2 (ShowsPrecSym2 :: Natural -> a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Natural) (y :: a). Sing x -> Sing y -> Sing (ShowsPrecSym2 x y) #

SingI t => SingI ('Text t :: ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ('Text t) #

SingI1 ShowParenSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (ShowParenSym1 x) #

SingI1 ShowCharSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Char). Sing x -> Sing (ShowCharSym1 x) #

SingI1 ConsSymbolSym1 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

liftSing :: forall (x :: Char). Sing x -> Sing (ConsSymbolSym1 x) #

SingI1 ShowStringSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol). Sing x -> Sing (ShowStringSym1 x) #

SingI1 ((:$$:@#@$$) :: ErrorMessage' Symbol -> TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing ((:$$:@#@$$) x) #

SingI1 ((:<>:@#@$$) :: ErrorMessage' Symbol -> TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

liftSing :: forall (x :: PErrorMessage). Sing x -> Sing ((:<>:@#@$$) x) #

SShow a => SingI1 (ShowsPrecSym1 :: Natural -> TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ShowsPrecSym1 x :: TyFun a (Symbol ~> Symbol) -> Type) #

SShow a => SingI1 (ShowsSym1 :: a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsSym1 x) #

(SShow a, SingI d) => SingI1 (ShowsPrecSym2 d :: a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsPrecSym2 d x) #

SingI2 ShowParenSym2 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Bool) (y :: Symbol ~> Symbol). Sing x -> Sing y -> Sing (ShowParenSym2 x y) #

(SingI e1, SingI e2) => SingI (e1 ':$$: e2 :: ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing (e1 ':$$: e2) #

(SingI e1, SingI e2) => SingI (e1 ':<>: e2 :: ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing (e1 ':<>: e2) #

SingI ty => SingI ('ShowType ty :: ErrorMessage' Symbol) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ('ShowType ty :: ErrorMessage' Symbol) #

SShow a => SingI1 (ShowListSym1 :: [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListSym1 x) #

SingI d => SingI1 (ShowListWithSym2 d :: [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListWithSym2 d x) #

SingI ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI UnlinesSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI UnwordsSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowCommaSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ShowSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI ConsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingI UnconsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ConsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings UnlinesSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings UnwordsSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings UnconsSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings KnownSymbolSym0 Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings ShowCommaSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SingI d => SingI (ShowParenSym1 d :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym1 d) #

SingI (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) #

SingI ((:$$:@#@$) :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol ~> ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI ((:<>:@#@$) :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol ~> ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SShow a => SingI (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SShow a => SingI (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) #

SingI (TextSym0 :: TyFun Symbol (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI d => SingI (ShowCharSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowCharSym1 d) #

SingI d => SingI (ShowStringSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowStringSym1 d) #

SIsString a => SingI (FromStringSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in Data.String.Singletons

Methods

sing :: Sing (FromStringSym0 :: TyFun Symbol a -> Type) #

SingI (ErrorSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing (ErrorSym0 :: TyFun Symbol a -> Type) #

SingI (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SShow a => SingI (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) #

SShow a => SingI (Show_Sym0 :: TyFun a Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (Show_Sym0 :: TyFun a Symbol -> Type) #

SingI (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SingI x => SingI (ConsSymbolSym1 x :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

sing :: Sing (ConsSymbolSym1 x) #

SuppressUnusedWarnings (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ConsSymbolSym1 a6989586621679381116 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (FromStringSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in Data.String.Singletons

SuppressUnusedWarnings (ErrorSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (Show_Sym0 :: TyFun a Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SingI2 (ShowListWithSym2 :: (a ~> (Symbol ~> Symbol)) -> [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: a ~> (Symbol ~> Symbol)) (y :: [a]). Sing x -> Sing y -> Sing (ShowListWithSym2 x y) #

SingI x => SingI ((:$$:@#@$$) x :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ((:$$:@#@$$) x) #

SingI x => SingI ((:<>:@#@$$) x :: TyFun (ErrorMessage' Symbol) (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

Methods

sing :: Sing ((:<>:@#@$$) x) #

SingI d => SingI (ShowListWithSym1 d :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym1 d) #

(SShow a, SingI d) => SingI (ShowListSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym1 d) #

(SingI d1, SingI d2) => SingI (ShowParenSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym2 d1 d2) #

(SShow a, SingI d) => SingI (ShowsSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym1 d) #

(SShow a, SingI d) => SingI (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) #

SingI (ShowTypeSym0 :: TyFun t (ErrorMessage' Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings (ShowListWithSym1 a6989586621679807383 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SingI d => SingI1 (ShowParenSym2 d :: (Symbol ~> Symbol) -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol ~> Symbol). Sing x -> Sing (ShowParenSym2 d x) #

SingI1 (ShowListWithSym1 :: (a ~> (Symbol ~> Symbol)) -> TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a ~> (Symbol ~> Symbol)). Sing x -> Sing (ShowListWithSym1 x) #

(SingI d1, SingI d2) => SingI (ShowListWithSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym2 d1 d2) #

(SShow a, SingI d1, SingI d2) => SingI (ShowsPrecSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym2 d1 d2) #

SuppressUnusedWarnings (ShowListWithSym2 a6989586621679807383 a6989586621679807384 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type DemoteRep Symbol # 
Instance details

Defined in GHC.Internal.Generics

type DemoteRep Symbol = String
data Sing (s :: Symbol) # 
Instance details

Defined in GHC.Internal.Generics

data Sing (s :: Symbol) where
type Demote PErrorMessage Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Demote Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SSymbol
type Mempty Source # 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
type Mconcat (arg :: [Symbol]) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (arg :: [Symbol])
type Sconcat (arg :: NonEmpty Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sconcat (arg :: NonEmpty Symbol)
type FromString a Source # 
Instance details

Defined in Data.String.Singletons

type FromString a = a
type Show_ (arg :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Symbol)
type Compare (a :: Symbol) (b :: Symbol) # 
Instance details

Defined in GHC.Internal.Data.Type.Ord

type Compare (a :: Symbol) (b :: Symbol) = CmpSymbol a b
type (arg :: Symbol) /= (arg1 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) /= (arg1 :: Symbol)
type (x :: Symbol) == (y :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (x :: Symbol) == (y :: Symbol) = DefaultEq x y
type Mappend (arg1 :: Symbol) (arg2 :: Symbol) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: Symbol) (arg2 :: Symbol)
type (arg :: Symbol) < (arg1 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) < (arg1 :: Symbol)
type (arg :: Symbol) <= (arg1 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) <= (arg1 :: Symbol)
type (arg :: Symbol) > (arg1 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) > (arg1 :: Symbol)
type (arg :: Symbol) >= (arg1 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) >= (arg1 :: Symbol)
type Compare (a :: Symbol) (b :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Compare (a :: Symbol) (b :: Symbol) = CmpSymbol a b
type Max (arg :: Symbol) (arg1 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Max (arg :: Symbol) (arg1 :: Symbol)
type Min (arg :: Symbol) (arg1 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Min (arg :: Symbol) (arg1 :: Symbol)
type (a :: Symbol) <> (b :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (a :: Symbol) <> (b :: Symbol) = AppendSymbol a b
type ShowList (arg1 :: [Symbol]) arg2 Source # 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Symbol]) arg2
type Apply KnownSymbolSym0 (a6989586621679377839 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply KnownSymbolSym0 (a6989586621679377839 :: Symbol) = KnownSymbol a6989586621679377839
type Apply ShowCommaSpaceSym0 (a6989586621679807326 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCommaSpaceSym0 (a6989586621679807326 :: Symbol) = ShowCommaSpace a6989586621679807326
type Apply ShowSpaceSym0 (a6989586621679807332 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowSpaceSym0 (a6989586621679807332 :: Symbol) = ShowSpace a6989586621679807332
type ShowsPrec _1 (s :: Symbol) x Source # 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec _1 (s :: Symbol) x
type Apply (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) (a6989586621679803716 :: PErrorMessage) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply (TypeErrorSym0 :: TyFun PErrorMessage a -> Type) (a6989586621679803716 :: PErrorMessage) = TypeError a6989586621679803716 :: a
type Apply (ConsSymbolSym1 a6989586621679381116 :: TyFun Symbol Symbol -> Type) (a6989586621679381117 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (ConsSymbolSym1 a6989586621679381116 :: TyFun Symbol Symbol -> Type) (a6989586621679381117 :: Symbol) = ConsSymbol a6989586621679381116 a6989586621679381117
type Apply (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) (a6989586621679807376 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) (a6989586621679807376 :: Symbol) = ShowChar a6989586621679807375 a6989586621679807376
type Apply (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) (a6989586621679807365 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) (a6989586621679807365 :: Symbol) = ShowString a6989586621679807364 a6989586621679807365
type Apply (FromStringSym0 :: TyFun Symbol a -> Type) (a6989586621680338575 :: Symbol) Source # 
Instance details

Defined in Data.String.Singletons

type Apply (FromStringSym0 :: TyFun Symbol a -> Type) (a6989586621680338575 :: Symbol) = FromString a6989586621680338575 :: a
type Apply (ErrorSym0 :: TyFun Symbol a -> Type) (a6989586621679368947 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorSym0 :: TyFun Symbol a -> Type) (a6989586621679368947 :: Symbol) = Error a6989586621679368947 :: a
type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) (a6989586621679369227 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) (a6989586621679369227 :: Symbol) = ErrorWithoutStackTrace a6989586621679369227 :: a
type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621679807414 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621679807414 :: a) = Show_ a6989586621679807414
type Apply (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) (a6989586621679807419 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) (a6989586621679807419 :: Symbol) = ShowList a6989586621679807418 a6989586621679807419
type Apply (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) (a6989586621679807348 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) (a6989586621679807348 :: Symbol) = ShowParen a6989586621679807346 a6989586621679807347 a6989586621679807348
type Apply (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) (a6989586621679807402 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) (a6989586621679807402 :: Symbol) = Shows a6989586621679807401 a6989586621679807402
type Apply (ShowListWithSym2 a6989586621679807383 a6989586621679807384 :: TyFun Symbol Symbol -> Type) (a6989586621679807385 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym2 a6989586621679807383 a6989586621679807384 :: TyFun Symbol Symbol -> Type) (a6989586621679807385 :: Symbol) = ShowListWith a6989586621679807383 a6989586621679807384 a6989586621679807385
type Apply (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) (a6989586621679807411 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) (a6989586621679807411 :: Symbol) = ShowsPrec a6989586621679807409 a6989586621679807410 a6989586621679807411
type Apply UnconsSymbolSym0 (a6989586621679381627 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply UnconsSymbolSym0 (a6989586621679381627 :: Symbol) = UnconsSymbol a6989586621679381627
type Apply ShowParenSym0 (a6989586621679807346 :: Bool) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowParenSym0 (a6989586621679807346 :: Bool) = ShowParenSym1 a6989586621679807346
type Apply ConsSymbolSym0 (a6989586621679381116 :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply ConsSymbolSym0 (a6989586621679381116 :: Char) = ConsSymbolSym1 a6989586621679381116
type Apply ShowCharSym0 (a6989586621679807375 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621679807375 :: Char) = ShowCharSym1 a6989586621679807375
type Apply ShowStringSym0 (a6989586621679807364 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621679807364 :: Symbol) = ShowStringSym1 a6989586621679807364
type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807409 :: Natural) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807409 :: Natural) = ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type
type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807401 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807401 :: a) = ShowsSym1 a6989586621679807401
type Apply (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807410 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807410 :: a) = ShowsPrecSym2 a6989586621679807409 a6989586621679807410
type Apply UnlinesSym0 (a6989586621679544819 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnlinesSym0 (a6989586621679544819 :: [Symbol]) = Unlines a6989586621679544819
type Apply UnwordsSym0 (a6989586621679544809 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnwordsSym0 (a6989586621679544809 :: [Symbol]) = Unwords a6989586621679544809
type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807418 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807418 :: [a]) = ShowListSym1 a6989586621679807418
type Apply (ShowListWithSym1 a6989586621679807383 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807384 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym1 a6989586621679807383 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807384 :: [a]) = ShowListWithSym2 a6989586621679807383 a6989586621679807384
type Apply (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621679807347 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621679807347 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621679807346 a6989586621679807347
type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807383 :: a ~> (Symbol ~> Symbol)) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807383 :: a ~> (Symbol ~> Symbol)) = ShowListWithSym1 a6989586621679807383

data SList (a1 :: [a]) where Source #

Constructors

SNil :: forall a. SList ('[] :: [a]) 
SCons :: forall a (n1 :: a) (n2 :: [a]). Sing n1 -> Sing n2 -> SList (n1 ': n2) infixr 5 

Instances

Instances details
(SDecide a, SDecide [a]) => TestCoercion (SList :: [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: [a]) (b :: [a]). SList a0 -> SList b -> Maybe (Coercion a0 b) #

(SDecide a, SDecide [a]) => TestEquality (SList :: [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: [a]) (b :: [a]). SList a0 -> SList b -> Maybe (a0 :~: b) #

(ShowSing a, ShowSing [a]) => Show (SList z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> SList z -> ShowS #

show :: SList z -> String #

showList :: [SList z] -> ShowS #

Eq (SList z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: SList z -> SList z -> Bool #

(/=) :: SList z -> SList z -> Bool #

Tuples

data STuple0 (a :: ()) where Source #

Constructors

STuple0 :: STuple0 '() 

Instances

Instances details
TestCoercion STuple0 Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a :: ()) (b :: ()). STuple0 a -> STuple0 b -> Maybe (Coercion a b) #

TestEquality STuple0 Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a :: ()) (b :: ()). STuple0 a -> STuple0 b -> Maybe (a :~: b) #

Show (STuple0 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple0 z -> ShowS #

show :: STuple0 z -> String #

showList :: [STuple0 z] -> ShowS #

Eq (STuple0 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: STuple0 z -> STuple0 z -> Bool #

(/=) :: STuple0 z -> STuple0 z -> Bool #

data STuple2 (a1 :: (a, b)) where Source #

Constructors

STuple2 :: forall a b (n1 :: a) (n2 :: b). Sing n1 -> Sing n2 -> STuple2 '(n1, n2) 

Instances

Instances details
(SDecide a, SDecide b) => TestCoercion (STuple2 :: (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: (a, b)) (b0 :: (a, b)). STuple2 a0 -> STuple2 b0 -> Maybe (Coercion a0 b0) #

(SDecide a, SDecide b) => TestEquality (STuple2 :: (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: (a, b)) (b0 :: (a, b)). STuple2 a0 -> STuple2 b0 -> Maybe (a0 :~: b0) #

(ShowSing a, ShowSing b) => Show (STuple2 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple2 z -> ShowS #

show :: STuple2 z -> String #

showList :: [STuple2 z] -> ShowS #

Eq (STuple2 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: STuple2 z -> STuple2 z -> Bool #

(/=) :: STuple2 z -> STuple2 z -> Bool #

data STuple3 (a1 :: (a, b, c)) where Source #

Constructors

STuple3 :: forall a b c (n1 :: a) (n2 :: b) (n3 :: c). Sing n1 -> Sing n2 -> Sing n3 -> STuple3 '(n1, n2, n3) 

Instances

Instances details
(SDecide a, SDecide b, SDecide c) => TestCoercion (STuple3 :: (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: (a, b, c)) (b0 :: (a, b, c)). STuple3 a0 -> STuple3 b0 -> Maybe (Coercion a0 b0) #

(SDecide a, SDecide b, SDecide c) => TestEquality (STuple3 :: (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: (a, b, c)) (b0 :: (a, b, c)). STuple3 a0 -> STuple3 b0 -> Maybe (a0 :~: b0) #

(ShowSing a, ShowSing b, ShowSing c) => Show (STuple3 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple3 z -> ShowS #

show :: STuple3 z -> String #

showList :: [STuple3 z] -> ShowS #

Eq (STuple3 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: STuple3 z -> STuple3 z -> Bool #

(/=) :: STuple3 z -> STuple3 z -> Bool #

data STuple4 (a1 :: (a, b, c, d)) where Source #

Constructors

STuple4 :: forall a b c d (n1 :: a) (n2 :: b) (n3 :: c) (n4 :: d). Sing n1 -> Sing n2 -> Sing n3 -> Sing n4 -> STuple4 '(n1, n2, n3, n4) 

Instances

Instances details
(SDecide a, SDecide b, SDecide c, SDecide d) => TestCoercion (STuple4 :: (a, b, c, d) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: (a, b, c, d)) (b0 :: (a, b, c, d)). STuple4 a0 -> STuple4 b0 -> Maybe (Coercion a0 b0) #

(SDecide a, SDecide b, SDecide c, SDecide d) => TestEquality (STuple4 :: (a, b, c, d) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: (a, b, c, d)) (b0 :: (a, b, c, d)). STuple4 a0 -> STuple4 b0 -> Maybe (a0 :~: b0) #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d) => Show (STuple4 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple4 z -> ShowS #

show :: STuple4 z -> String #

showList :: [STuple4 z] -> ShowS #

Eq (STuple4 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: STuple4 z -> STuple4 z -> Bool #

(/=) :: STuple4 z -> STuple4 z -> Bool #

data STuple5 (a1 :: (a, b, c, d, e)) where Source #

Constructors

STuple5 :: forall a b c d e (n1 :: a) (n2 :: b) (n3 :: c) (n4 :: d) (n5 :: e). Sing n1 -> Sing n2 -> Sing n3 -> Sing n4 -> Sing n5 -> STuple5 '(n1, n2, n3, n4, n5) 

Instances

Instances details
(SDecide a, SDecide b, SDecide c, SDecide d, SDecide e) => TestCoercion (STuple5 :: (a, b, c, d, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: (a, b, c, d, e)) (b0 :: (a, b, c, d, e)). STuple5 a0 -> STuple5 b0 -> Maybe (Coercion a0 b0) #

(SDecide a, SDecide b, SDecide c, SDecide d, SDecide e) => TestEquality (STuple5 :: (a, b, c, d, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: (a, b, c, d, e)) (b0 :: (a, b, c, d, e)). STuple5 a0 -> STuple5 b0 -> Maybe (a0 :~: b0) #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e) => Show (STuple5 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple5 z -> ShowS #

show :: STuple5 z -> String #

showList :: [STuple5 z] -> ShowS #

Eq (STuple5 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: STuple5 z -> STuple5 z -> Bool #

(/=) :: STuple5 z -> STuple5 z -> Bool #

data STuple6 (a1 :: (a, b, c, d, e, f)) where Source #

Constructors

STuple6 :: forall a b c d e f (n1 :: a) (n2 :: b) (n3 :: c) (n4 :: d) (n5 :: e) (n6 :: f). Sing n1 -> Sing n2 -> Sing n3 -> Sing n4 -> Sing n5 -> Sing n6 -> STuple6 '(n1, n2, n3, n4, n5, n6) 

Instances

Instances details
(SDecide a, SDecide b, SDecide c, SDecide d, SDecide e, SDecide f) => TestCoercion (STuple6 :: (a, b, c, d, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: (a, b, c, d, e, f)) (b0 :: (a, b, c, d, e, f)). STuple6 a0 -> STuple6 b0 -> Maybe (Coercion a0 b0) #

(SDecide a, SDecide b, SDecide c, SDecide d, SDecide e, SDecide f) => TestEquality (STuple6 :: (a, b, c, d, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: (a, b, c, d, e, f)) (b0 :: (a, b, c, d, e, f)). STuple6 a0 -> STuple6 b0 -> Maybe (a0 :~: b0) #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f) => Show (STuple6 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple6 z -> ShowS #

show :: STuple6 z -> String #

showList :: [STuple6 z] -> ShowS #

Eq (STuple6 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: STuple6 z -> STuple6 z -> Bool #

(/=) :: STuple6 z -> STuple6 z -> Bool #

data STuple7 (a1 :: (a, b, c, d, e, f, g)) where Source #

Constructors

STuple7 :: forall a b c d e f g (n1 :: a) (n2 :: b) (n3 :: c) (n4 :: d) (n5 :: e) (n6 :: f) (n7 :: g). Sing n1 -> Sing n2 -> Sing n3 -> Sing n4 -> Sing n5 -> Sing n6 -> Sing n7 -> STuple7 '(n1, n2, n3, n4, n5, n6, n7) 

Instances

Instances details
(SDecide a, SDecide b, SDecide c, SDecide d, SDecide e, SDecide f, SDecide g) => TestCoercion (STuple7 :: (a, b, c, d, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testCoercion :: forall (a0 :: (a, b, c, d, e, f, g)) (b0 :: (a, b, c, d, e, f, g)). STuple7 a0 -> STuple7 b0 -> Maybe (Coercion a0 b0) #

(SDecide a, SDecide b, SDecide c, SDecide d, SDecide e, SDecide f, SDecide g) => TestEquality (STuple7 :: (a, b, c, d, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

testEquality :: forall (a0 :: (a, b, c, d, e, f, g)) (b0 :: (a, b, c, d, e, f, g)). STuple7 a0 -> STuple7 b0 -> Maybe (a0 :~: b0) #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f, ShowSing g) => Show (STuple7 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

showsPrec :: Int -> STuple7 z -> ShowS #

show :: STuple7 z -> String #

showList :: [STuple7 z] -> ShowS #

Eq (STuple7 z) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

(==) :: STuple7 z -> STuple7 z -> Bool #

(/=) :: STuple7 z -> STuple7 z -> Bool #

type family Fst (a1 :: (a, b)) :: a where ... Source #

Equations

Fst ('(x, _1) :: (a, b)) = x 

sFst :: forall a b (t :: (a, b)). Sing t -> Sing (Fst t) Source #

type family Snd (a1 :: (a, b)) :: b where ... Source #

Equations

Snd ('(_1, y) :: (a, b)) = y 

sSnd :: forall a b (t :: (a, b)). Sing t -> Sing (Snd t) Source #

type family Curry (a1 :: (a, b) ~> c) (a2 :: a) (a3 :: b) :: c where ... Source #

Equations

Curry (f :: (k2, k3) ~> k4) (x :: k2) (y :: k3) = Apply f (Apply (Apply (Tuple2Sym0 :: TyFun k2 (k3 ~> (k2, k3)) -> Type) x) y) 

sCurry :: forall a b c (t1 :: (a, b) ~> c) (t2 :: a) (t3 :: b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Curry t1 t2 t3) Source #

type family Uncurry (a1 :: a ~> (b ~> c)) (a2 :: (a, b)) :: c where ... Source #

Equations

Uncurry (f :: a ~> (k1 ~> k3)) (p :: (a, k1)) = Apply (Apply f (Apply (FstSym0 :: TyFun (a, k1) a -> Type) p)) (Apply (SndSym0 :: TyFun (a, k1) k1 -> Type) p) 

sUncurry :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Uncurry t1 t2) Source #

Basic type classes

class PEq a Source #

Associated Types

type (arg :: a) == (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) == (arg1 :: a) = TFHelper_6989586621679128045 arg arg1

type (arg :: a) /= (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) /= (arg1 :: a) = TFHelper_6989586621679128034 arg arg1

Instances

Instances details
PEq Void Source # 
Instance details

Defined in Data.Eq.Singletons

Associated Types

type (a1 :: Void) == (a2 :: Void) 
Instance details

Defined in Data.Eq.Singletons

type (a1 :: Void) == (a2 :: Void)
type (arg1 :: Void) /= (arg2 :: Void) 
Instance details

Defined in Data.Eq.Singletons

type (arg1 :: Void) /= (arg2 :: Void)
PEq All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a1 :: All) == (a2 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: All) == (a2 :: All)
type (arg :: All) /= (arg1 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: All) /= (arg1 :: All)
PEq Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a1 :: Any) == (a2 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: Any) == (a2 :: Any)
type (arg :: Any) /= (arg1 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Any) /= (arg1 :: Any)
PEq Ordering Source # 
Instance details

Defined in Data.Eq.Singletons

Associated Types

type (a1 :: Ordering) == (a2 :: Ordering) 
Instance details

Defined in Data.Eq.Singletons

type (a1 :: Ordering) == (a2 :: Ordering)
type (arg1 :: Ordering) /= (arg2 :: Ordering) 
Instance details

Defined in Data.Eq.Singletons

type (arg1 :: Ordering) /= (arg2 :: Ordering)
PEq Natural Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type (x :: Natural) == (y :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (x :: Natural) == (y :: Natural) = DefaultEq x y
type (arg :: Natural) /= (arg1 :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Natural) /= (arg1 :: Natural)
PEq () Source # 
Instance details

Defined in Data.Eq.Singletons

Associated Types

type (a1 :: ()) == (a2 :: ()) 
Instance details

Defined in Data.Eq.Singletons

type (a1 :: ()) == (a2 :: ())
type (arg1 :: ()) /= (arg2 :: ()) 
Instance details

Defined in Data.Eq.Singletons

type (arg1 :: ()) /= (arg2 :: ())
PEq Bool Source # 
Instance details

Defined in Data.Eq.Singletons

Associated Types

type (a1 :: Bool) == (a2 :: Bool) 
Instance details

Defined in Data.Eq.Singletons

type (a1 :: Bool) == (a2 :: Bool)
type (arg1 :: Bool) /= (arg2 :: Bool) 
Instance details

Defined in Data.Eq.Singletons

type (arg1 :: Bool) /= (arg2 :: Bool)
PEq Char Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type (x :: Char) == (y :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (x :: Char) == (y :: Char) = DefaultEq x y
type (arg :: Char) /= (arg1 :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Char) /= (arg1 :: Char)
PEq Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type (x :: Symbol) == (y :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (x :: Symbol) == (y :: Symbol) = DefaultEq x y
type (arg :: Symbol) /= (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) /= (arg1 :: Symbol)
PEq (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PEq (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PEq (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PEq (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PEq (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PEq (NonEmpty a) Source # 
Instance details

Defined in Data.Eq.Singletons

PEq (Identity a) Source # 
Instance details

Defined in Data.Eq.Singletons

PEq (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PEq (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PEq (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

PEq (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PEq (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PEq (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PEq (Maybe a) Source # 
Instance details

Defined in Data.Eq.Singletons

PEq (TYPE rep) Source # 
Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

PEq [a] Source # 
Instance details

Defined in Data.Eq.Singletons

PEq (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PEq (Either a b) Source # 
Instance details

Defined in Data.Eq.Singletons

PEq (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

PEq (a, b) Source # 
Instance details

Defined in Data.Eq.Singletons

PEq (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

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

Defined in Data.Eq.Singletons

PEq (Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

PEq (Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

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

Defined in Data.Eq.Singletons

PEq (Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

class SEq a where Source #

Minimal complete definition

Nothing

Methods

(%==) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 == t2) infix 4 Source #

default (%==) :: forall (t1 :: a) (t2 :: a). (t1 == t2) ~ TFHelper_6989586621679128045 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) infix 4 Source #

default (%/=) :: forall (t1 :: a) (t2 :: a). (t1 /= t2) ~ TFHelper_6989586621679128034 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

Instances

Instances details
SEq Void Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq Bool => SEq All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq Bool => SEq Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq Ordering Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq Natural Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

(%==) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq () Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq Bool Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq Char Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

(%==) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

(%==) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq m => SEq (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq [a]) => SEq (NonEmpty a) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Identity a) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq (Maybe a) => SEq (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

(%==) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq (Maybe a) => SEq (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

(%==) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

(%==) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%==) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Maybe a) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq (TYPE rep) Source # 
Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

Methods

(%==) :: forall (t1 :: TYPE rep) (t2 :: TYPE rep). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: TYPE rep) (t2 :: TYPE rep). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq [a]) => SEq [a] Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%==) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq b) => SEq (Either a b) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

(%==) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq b) => SEq (a, b) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq a => SEq (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

(%==) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq b, SEq c) => SEq (a, b, c) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq (f a), SEq (g a)) => SEq (Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

(%==) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq (f a), SEq (g a)) => SEq (Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

(%==) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq b, SEq c, SEq d) => SEq (a, b, c, d) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

SEq (f (g a)) => SEq (Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

(%==) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq b, SEq c, SEq d, SEq e) => SEq (a, b, c, d, e) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq b, SEq c, SEq d, SEq e, SEq f) => SEq (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

(SEq a, SEq b, SEq c, SEq d, SEq e, SEq f, SEq g) => SEq (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (t1 == t2) Source #

(%/=) :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (t1 /= t2) Source #

class POrd a Source #

Associated Types

type Compare (arg :: a) (arg1 :: a) :: Ordering Source #

type Compare (arg :: a) (arg1 :: a) = Compare_6989586621679190000 arg arg1

type (arg :: a) < (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) < (arg1 :: a) = TFHelper_6989586621679190021 arg arg1

type (arg :: a) <= (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) <= (arg1 :: a) = TFHelper_6989586621679190037 arg arg1

type (arg :: a) > (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) > (arg1 :: a) = TFHelper_6989586621679190053 arg arg1

type (arg :: a) >= (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) >= (arg1 :: a) = TFHelper_6989586621679190069 arg arg1

type Max (arg :: a) (arg1 :: a) :: a Source #

type Max (arg :: a) (arg1 :: a) = Max_6989586621679190085 arg arg1

type Min (arg :: a) (arg1 :: a) :: a Source #

type Min (arg :: a) (arg1 :: a) = Min_6989586621679190101 arg arg1

Instances

Instances details
POrd Void Source # 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type Compare (a1 :: Void) (a2 :: Void) 
Instance details

Defined in Data.Ord.Singletons

type Compare (a1 :: Void) (a2 :: Void)
type (arg1 :: Void) < (arg2 :: Void) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Void) < (arg2 :: Void)
type (arg1 :: Void) <= (arg2 :: Void) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Void) <= (arg2 :: Void)
type (arg1 :: Void) > (arg2 :: Void) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Void) > (arg2 :: Void)
type (arg1 :: Void) >= (arg2 :: Void) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Void) >= (arg2 :: Void)
type Max (arg1 :: Void) (arg2 :: Void) 
Instance details

Defined in Data.Ord.Singletons

type Max (arg1 :: Void) (arg2 :: Void)
type Min (arg1 :: Void) (arg2 :: Void) 
Instance details

Defined in Data.Ord.Singletons

type Min (arg1 :: Void) (arg2 :: Void)
POrd All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Compare (a1 :: All) (a2 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Compare (a1 :: All) (a2 :: All)
type (arg :: All) < (arg1 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: All) < (arg1 :: All)
type (arg :: All) <= (arg1 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: All) <= (arg1 :: All)
type (arg :: All) > (arg1 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: All) > (arg1 :: All)
type (arg :: All) >= (arg1 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: All) >= (arg1 :: All)
type Max (arg :: All) (arg1 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Max (arg :: All) (arg1 :: All)
type Min (arg :: All) (arg1 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Min (arg :: All) (arg1 :: All)
POrd Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Compare (a1 :: Any) (a2 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Compare (a1 :: Any) (a2 :: Any)
type (arg :: Any) < (arg1 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Any) < (arg1 :: Any)
type (arg :: Any) <= (arg1 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Any) <= (arg1 :: Any)
type (arg :: Any) > (arg1 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Any) > (arg1 :: Any)
type (arg :: Any) >= (arg1 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Any) >= (arg1 :: Any)
type Max (arg :: Any) (arg1 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Max (arg :: Any) (arg1 :: Any)
type Min (arg :: Any) (arg1 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Min (arg :: Any) (arg1 :: Any)
POrd Ordering Source # 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type Compare (a1 :: Ordering) (a2 :: Ordering) 
Instance details

Defined in Data.Ord.Singletons

type Compare (a1 :: Ordering) (a2 :: Ordering)
type (arg1 :: Ordering) < (arg2 :: Ordering) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Ordering) < (arg2 :: Ordering)
type (arg1 :: Ordering) <= (arg2 :: Ordering) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Ordering) <= (arg2 :: Ordering)
type (arg1 :: Ordering) > (arg2 :: Ordering) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Ordering) > (arg2 :: Ordering)
type (arg1 :: Ordering) >= (arg2 :: Ordering) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Ordering) >= (arg2 :: Ordering)
type Max (arg1 :: Ordering) (arg2 :: Ordering) 
Instance details

Defined in Data.Ord.Singletons

type Max (arg1 :: Ordering) (arg2 :: Ordering)
type Min (arg1 :: Ordering) (arg2 :: Ordering) 
Instance details

Defined in Data.Ord.Singletons

type Min (arg1 :: Ordering) (arg2 :: Ordering)
POrd Natural Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type Compare (a :: Natural) (b :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Compare (a :: Natural) (b :: Natural) = CmpNat a b
type (arg :: Natural) < (arg1 :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Natural) < (arg1 :: Natural)
type (arg :: Natural) <= (arg1 :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Natural) <= (arg1 :: Natural)
type (arg :: Natural) > (arg1 :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Natural) > (arg1 :: Natural)
type (arg :: Natural) >= (arg1 :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Natural) >= (arg1 :: Natural)
type Max (arg :: Natural) (arg1 :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Max (arg :: Natural) (arg1 :: Natural)
type Min (arg :: Natural) (arg1 :: Natural) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Min (arg :: Natural) (arg1 :: Natural)
POrd () Source # 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type Compare (a1 :: ()) (a2 :: ()) 
Instance details

Defined in Data.Ord.Singletons

type Compare (a1 :: ()) (a2 :: ())
type (arg1 :: ()) < (arg2 :: ()) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: ()) < (arg2 :: ())
type (arg1 :: ()) <= (arg2 :: ()) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: ()) <= (arg2 :: ())
type (arg1 :: ()) > (arg2 :: ()) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: ()) > (arg2 :: ())
type (arg1 :: ()) >= (arg2 :: ()) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: ()) >= (arg2 :: ())
type Max (arg1 :: ()) (arg2 :: ()) 
Instance details

Defined in Data.Ord.Singletons

type Max (arg1 :: ()) (arg2 :: ())
type Min (arg1 :: ()) (arg2 :: ()) 
Instance details

Defined in Data.Ord.Singletons

type Min (arg1 :: ()) (arg2 :: ())
POrd Bool Source # 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type Compare (a1 :: Bool) (a2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type Compare (a1 :: Bool) (a2 :: Bool)
type (arg1 :: Bool) < (arg2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Bool) < (arg2 :: Bool)
type (arg1 :: Bool) <= (arg2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Bool) <= (arg2 :: Bool)
type (arg1 :: Bool) > (arg2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Bool) > (arg2 :: Bool)
type (arg1 :: Bool) >= (arg2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type (arg1 :: Bool) >= (arg2 :: Bool)
type Max (arg1 :: Bool) (arg2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type Max (arg1 :: Bool) (arg2 :: Bool)
type Min (arg1 :: Bool) (arg2 :: Bool) 
Instance details

Defined in Data.Ord.Singletons

type Min (arg1 :: Bool) (arg2 :: Bool)
POrd Char Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type Compare (a :: Char) (b :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Compare (a :: Char) (b :: Char) = CmpChar a b
type (arg :: Char) < (arg1 :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Char) < (arg1 :: Char)
type (arg :: Char) <= (arg1 :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Char) <= (arg1 :: Char)
type (arg :: Char) > (arg1 :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Char) > (arg1 :: Char)
type (arg :: Char) >= (arg1 :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Char) >= (arg1 :: Char)
type Max (arg :: Char) (arg1 :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Max (arg :: Char) (arg1 :: Char)
type Min (arg :: Char) (arg1 :: Char) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Min (arg :: Char) (arg1 :: Char)
POrd Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type Compare (a :: Symbol) (b :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Compare (a :: Symbol) (b :: Symbol) = CmpSymbol a b
type (arg :: Symbol) < (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) < (arg1 :: Symbol)
type (arg :: Symbol) <= (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) <= (arg1 :: Symbol)
type (arg :: Symbol) > (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) > (arg1 :: Symbol)
type (arg :: Symbol) >= (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (arg :: Symbol) >= (arg1 :: Symbol)
type Max (arg :: Symbol) (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Max (arg :: Symbol) (arg1 :: Symbol)
type Min (arg :: Symbol) (arg1 :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Min (arg :: Symbol) (arg1 :: Symbol)
POrd (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

POrd (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

POrd (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

POrd (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

POrd (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

POrd (NonEmpty a) Source # 
Instance details

Defined in Data.Ord.Singletons

POrd (Identity a) Source # 
Instance details

Defined in Data.Ord.Singletons

POrd (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

POrd (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

POrd (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

POrd (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

POrd (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

POrd (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

POrd (Maybe a) Source # 
Instance details

Defined in Data.Ord.Singletons

POrd [a] Source # 
Instance details

Defined in Data.Ord.Singletons

POrd (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

POrd (Either a b) Source # 
Instance details

Defined in Data.Ord.Singletons

POrd (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

POrd (a, b) Source # 
Instance details

Defined in Data.Ord.Singletons

POrd (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

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

Defined in Data.Ord.Singletons

POrd (Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

POrd (Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

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

Defined in Data.Ord.Singletons

POrd (Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

class SEq a => SOrd a where Source #

Minimal complete definition

Nothing

Methods

sCompare :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

default sCompare :: forall (t1 :: a) (t2 :: a). Compare t1 t2 ~ Compare_6989586621679190000 t1 t2 => Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 < t2) infix 4 Source #

default (%<) :: forall (t1 :: a) (t2 :: a). (t1 < t2) ~ TFHelper_6989586621679190021 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) infix 4 Source #

default (%<=) :: forall (t1 :: a) (t2 :: a). (t1 <= t2) ~ TFHelper_6989586621679190037 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 > t2) infix 4 Source #

default (%>) :: forall (t1 :: a) (t2 :: a). (t1 > t2) ~ TFHelper_6989586621679190053 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) infix 4 Source #

default (%>=) :: forall (t1 :: a) (t2 :: a). (t1 >= t2) ~ TFHelper_6989586621679190069 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

default sMax :: forall (t1 :: a) (t2 :: a). Max t1 t2 ~ Max_6989586621679190085 t1 t2 => Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

default sMin :: forall (t1 :: a) (t2 :: a). Min t1 t2 ~ Min_6989586621679190101 t1 t2 => Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

Instances

Instances details
SOrd Void Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd Bool => SOrd All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd Bool => SOrd Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd Ordering Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd Natural Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sCompare :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd () Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd Bool Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd Char Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sCompare :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sCompare :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd m => SOrd (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd [a]) => SOrd (NonEmpty a) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Identity a) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd (Maybe a) => SOrd (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sCompare :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd (Maybe a) => SOrd (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sCompare :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sCompare :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Maybe a) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd [a]) => SOrd [a] Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sCompare :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd b) => SOrd (Either a b) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sCompare :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd b) => SOrd (a, b) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd a => SOrd (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sCompare :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd b, SOrd c) => SOrd (a, b, c) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd (f a), SOrd (g a)) => SOrd (Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sCompare :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd (f a), SOrd (g a)) => SOrd (Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sCompare :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd b, SOrd c, SOrd d) => SOrd (a, b, c, d) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

SOrd (f (g a)) => SOrd (Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sCompare :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e) => SOrd (a, b, c, d, e) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e, SOrd f) => SOrd (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

(SOrd a, SOrd b, SOrd c, SOrd d, SOrd e, SOrd f, SOrd g) => SOrd (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (Compare t1 t2) Source #

(%<) :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (t1 < t2) Source #

(%<=) :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (t1 <= t2) Source #

(%>) :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (t1 > t2) Source #

(%>=) :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (t1 >= t2) Source #

sMax :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (Max t1 t2) Source #

sMin :: forall (t1 :: (a, b, c, d, e, f, g)) (t2 :: (a, b, c, d, e, f, g)). Sing t1 -> Sing t2 -> Sing (Min t1 t2) Source #

As a matter of convenience, the Prelude.Singletons does not export promoted/singletonized succ and pred, due to likely conflicts with unary numbers. Please import Data.Singletons.Base.Enum directly if you want these.

class PEnum a Source #

Associated Types

type ToEnum (arg :: Natural) :: a Source #

type FromEnum (arg :: a) :: Natural Source #

type EnumFromTo (arg :: a) (arg1 :: a) :: [a] Source #

type EnumFromTo (arg :: a) (arg1 :: a) = EnumFromTo_6989586621679414102 arg arg1

type EnumFromThenTo (arg :: a) (arg1 :: a) (arg2 :: a) :: [a] Source #

type EnumFromThenTo (arg :: a) (arg1 :: a) (arg2 :: a) = EnumFromThenTo_6989586621679414114 arg arg1 arg2

Instances

Instances details
PEnum Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ (arg :: Ordering) 
Instance details

Defined in Data.Singletons.Base.Enum

type Succ (arg :: Ordering)
type Pred (arg :: Ordering) 
Instance details

Defined in Data.Singletons.Base.Enum

type Pred (arg :: Ordering)
type ToEnum a 
Instance details

Defined in Data.Singletons.Base.Enum

type ToEnum a
type FromEnum (a :: Ordering) 
Instance details

Defined in Data.Singletons.Base.Enum

type FromEnum (a :: Ordering)
type EnumFromTo (arg1 :: Ordering) (arg2 :: Ordering) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromTo (arg1 :: Ordering) (arg2 :: Ordering)
type EnumFromThenTo (arg1 :: Ordering) (arg2 :: Ordering) (arg3 :: Ordering) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromThenTo (arg1 :: Ordering) (arg2 :: Ordering) (arg3 :: Ordering)
PEnum Natural Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ (a :: Natural) 
Instance details

Defined in Data.Singletons.Base.Enum

type Succ (a :: Natural)
type Pred (a :: Natural) 
Instance details

Defined in Data.Singletons.Base.Enum

type Pred (a :: Natural)
type ToEnum a 
Instance details

Defined in Data.Singletons.Base.Enum

type ToEnum a
type FromEnum (a :: Natural) 
Instance details

Defined in Data.Singletons.Base.Enum

type FromEnum (a :: Natural)
type EnumFromTo (a1 :: Natural) (a2 :: Natural) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromTo (a1 :: Natural) (a2 :: Natural)
type EnumFromThenTo (a1 :: Natural) (a2 :: Natural) (a3 :: Natural) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromThenTo (a1 :: Natural) (a2 :: Natural) (a3 :: Natural)
PEnum () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ (arg :: ()) 
Instance details

Defined in Data.Singletons.Base.Enum

type Succ (arg :: ())
type Pred (arg :: ()) 
Instance details

Defined in Data.Singletons.Base.Enum

type Pred (arg :: ())
type ToEnum a 
Instance details

Defined in Data.Singletons.Base.Enum

type ToEnum a
type FromEnum (a :: ()) 
Instance details

Defined in Data.Singletons.Base.Enum

type FromEnum (a :: ())
type EnumFromTo (arg1 :: ()) (arg2 :: ()) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromTo (arg1 :: ()) (arg2 :: ())
type EnumFromThenTo (arg1 :: ()) (arg2 :: ()) (arg3 :: ()) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromThenTo (arg1 :: ()) (arg2 :: ()) (arg3 :: ())
PEnum Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ (arg :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

type Succ (arg :: Bool)
type Pred (arg :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

type Pred (arg :: Bool)
type ToEnum a 
Instance details

Defined in Data.Singletons.Base.Enum

type ToEnum a
type FromEnum (a :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

type FromEnum (a :: Bool)
type EnumFromTo (arg1 :: Bool) (arg2 :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromTo (arg1 :: Bool) (arg2 :: Bool)
type EnumFromThenTo (arg1 :: Bool) (arg2 :: Bool) (arg3 :: Bool) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromThenTo (arg1 :: Bool) (arg2 :: Bool) (arg3 :: Bool)
PEnum Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ (arg :: Char) 
Instance details

Defined in Data.Singletons.Base.Enum

type Succ (arg :: Char)
type Pred (arg :: Char) 
Instance details

Defined in Data.Singletons.Base.Enum

type Pred (arg :: Char)
type ToEnum a 
Instance details

Defined in Data.Singletons.Base.Enum

type ToEnum a
type FromEnum (a :: Char) 
Instance details

Defined in Data.Singletons.Base.Enum

type FromEnum (a :: Char)
type EnumFromTo (arg1 :: Char) (arg2 :: Char) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromTo (arg1 :: Char) (arg2 :: Char)
type EnumFromThenTo (arg1 :: Char) (arg2 :: Char) (arg3 :: Char) 
Instance details

Defined in Data.Singletons.Base.Enum

type EnumFromThenTo (arg1 :: Char) (arg2 :: Char) (arg3 :: Char)
PEnum (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PEnum (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PEnum (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PEnum (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PEnum (WrappedMonoid a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PEnum (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

PEnum (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

PEnum (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

class SEnum a where Source #

Minimal complete definition

sToEnum, sFromEnum

Methods

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: a) Source #

sFromEnum :: forall (t :: a). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

default sEnumFromTo :: forall (t1 :: a) (t2 :: a). EnumFromTo t1 t2 ~ EnumFromTo_6989586621679414102 t1 t2 => Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: a) (t2 :: a) (t3 :: a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

default sEnumFromThenTo :: forall (t1 :: a) (t2 :: a) (t3 :: a). EnumFromThenTo t1 t2 t3 ~ EnumFromThenTo_6989586621679414114 t1 t2 t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

Instances

Instances details
SEnum Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: Ordering). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Ordering). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Ordering) Source #

sFromEnum :: forall (t :: Ordering). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Ordering) (t2 :: Ordering) (t3 :: Ordering). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum Natural Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: Natural). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Natural). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Natural) Source #

sFromEnum :: forall (t :: Natural). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Natural) (t2 :: Natural) (t3 :: Natural). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: ()). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: ()). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: ()) Source #

sFromEnum :: forall (t :: ()). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: ()) (t2 :: ()) (t3 :: ()). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: Bool). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Bool). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Bool) Source #

sFromEnum :: forall (t :: Bool). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Bool) (t2 :: Bool) (t3 :: Bool). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: Char). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Char). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Char) Source #

sFromEnum :: forall (t :: Char). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Char) (t2 :: Char) (t3 :: Char). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum a => SEnum (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sSucc :: forall (t :: First a). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: First a). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: First a) Source #

sFromEnum :: forall (t :: First a). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: First a) (t2 :: First a) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum a => SEnum (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sSucc :: forall (t :: Last a). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Last a). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Last a) Source #

sFromEnum :: forall (t :: Last a). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Last a) (t2 :: Last a) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum a => SEnum (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sSucc :: forall (t :: Max a). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Max a). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Max a) Source #

sFromEnum :: forall (t :: Max a). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Max a) (t2 :: Max a) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum a => SEnum (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sSucc :: forall (t :: Min a). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Min a). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Min a) Source #

sFromEnum :: forall (t :: Min a). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Min a) (t2 :: Min a) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum a => SEnum (WrappedMonoid a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sSucc :: forall (t :: WrappedMonoid a). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: WrappedMonoid a). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: WrappedMonoid a) Source #

sFromEnum :: forall (t :: WrappedMonoid a). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: WrappedMonoid a) (t2 :: WrappedMonoid a). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: WrappedMonoid a) (t2 :: WrappedMonoid a) (t3 :: WrappedMonoid a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum a => SEnum (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sSucc :: forall (t :: Identity a). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Identity a). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Identity a) Source #

sFromEnum :: forall (t :: Identity a). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Identity a) (t2 :: Identity a) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sSucc :: forall (t :: Proxy s). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Proxy s). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Proxy s) Source #

sFromEnum :: forall (t :: Proxy s). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Proxy s) (t2 :: Proxy s) (t3 :: Proxy s). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

SEnum a => SEnum (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sSucc :: forall (t :: Const a b). Sing t -> Sing (Succ t) Source #

sPred :: forall (t :: Const a b). Sing t -> Sing (Pred t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (ToEnum t :: Const a b) Source #

sFromEnum :: forall (t :: Const a b). Sing t -> Sing (FromEnum t) Source #

sEnumFromTo :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (EnumFromTo t1 t2) Source #

sEnumFromThenTo :: forall (t1 :: Const a b) (t2 :: Const a b) (t3 :: Const a b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (EnumFromThenTo t1 t2 t3) Source #

class PBounded a Source #

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

Instances

Instances details
PBounded All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

PBounded () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

PBounded Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

PBounded Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

PBounded (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded (Identity a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

PBounded (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type MaxBound 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PBounded (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type MinBound 
Instance details

Defined in Data.Proxy.Singletons

type MaxBound 
Instance details

Defined in Data.Proxy.Singletons

PBounded (a, b) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

PBounded (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Associated Types

type MinBound 
Instance details

Defined in Data.Functor.Const.Singletons

type MaxBound 
Instance details

Defined in Data.Functor.Const.Singletons

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound 
Instance details

Defined in Data.Singletons.Base.Enum

type MaxBound 
Instance details

Defined in Data.Singletons.Base.Enum

class SBounded a where Source #

Instances

Instances details
SBounded Bool => SBounded All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded Bool => SBounded Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SBounded () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SBounded Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SBounded Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SBounded a => SBounded (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded a => SBounded (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded a => SBounded (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded a => SBounded (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded m => SBounded (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded a => SBounded (Identity a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SBounded a => SBounded (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded a => SBounded (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded a => SBounded (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

(SBounded a, SBounded b) => SBounded (a, b) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sMinBound :: Sing (MinBound :: (a, b)) Source #

sMaxBound :: Sing (MaxBound :: (a, b)) Source #

SBounded a => SBounded (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

(SBounded a, SBounded b, SBounded c) => SBounded (a, b, c) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sMinBound :: Sing (MinBound :: (a, b, c)) Source #

sMaxBound :: Sing (MaxBound :: (a, b, c)) Source #

(SBounded a, SBounded b, SBounded c, SBounded d) => SBounded (a, b, c, d) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sMinBound :: Sing (MinBound :: (a, b, c, d)) Source #

sMaxBound :: Sing (MaxBound :: (a, b, c, d)) Source #

(SBounded a, SBounded b, SBounded c, SBounded d, SBounded e) => SBounded (a, b, c, d, e) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sMinBound :: Sing (MinBound :: (a, b, c, d, e)) Source #

sMaxBound :: Sing (MaxBound :: (a, b, c, d, e)) Source #

(SBounded a, SBounded b, SBounded c, SBounded d, SBounded e, SBounded f) => SBounded (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sMinBound :: Sing (MinBound :: (a, b, c, d, e, f)) Source #

sMaxBound :: Sing (MaxBound :: (a, b, c, d, e, f)) Source #

(SBounded a, SBounded b, SBounded c, SBounded d, SBounded e, SBounded f, SBounded g) => SBounded (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sMinBound :: Sing (MinBound :: (a, b, c, d, e, f, g)) Source #

sMaxBound :: Sing (MaxBound :: (a, b, c, d, e, f, g)) Source #

Numbers

Numeric type classes

class PNum a Source #

Associated Types

type (arg :: a) + (arg1 :: a) :: a infixl 6 Source #

type (arg :: a) - (arg1 :: a) :: a infixl 6 Source #

type (arg :: a) - (arg1 :: a) = TFHelper_6989586621679398594 arg arg1

type (arg :: a) * (arg1 :: a) :: a infixl 7 Source #

type Negate (arg :: a) :: a Source #

type Negate (arg :: a) = Negate_6989586621679398604 arg

type Abs (arg :: a) :: a Source #

type Signum (arg :: a) :: a Source #

type FromInteger (arg :: Natural) :: a Source #

Instances

Instances details
PNum Natural Source # 
Instance details

Defined in GHC.Num.Singletons

Associated Types

type (a :: Natural) + (b :: Natural) 
Instance details

Defined in GHC.Num.Singletons

type (a :: Natural) + (b :: Natural) = a + b
type (a :: Natural) - (b :: Natural) 
Instance details

Defined in GHC.Num.Singletons

type (a :: Natural) - (b :: Natural) = a - b
type (a :: Natural) * (b :: Natural) 
Instance details

Defined in GHC.Num.Singletons

type (a :: Natural) * (b :: Natural) = a * b
type Negate (a :: Natural) 
Instance details

Defined in GHC.Num.Singletons

type Negate (a :: Natural) = Error "Cannot negate a natural number" :: Natural
type Abs (a :: Natural) 
Instance details

Defined in GHC.Num.Singletons

type Abs (a :: Natural) = a
type Signum (a :: Natural) 
Instance details

Defined in GHC.Num.Singletons

type Signum (a :: Natural)
type FromInteger a 
Instance details

Defined in GHC.Num.Singletons

type FromInteger a = a
PNum (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PNum (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PNum (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

PNum (Down a) Source # 
Instance details

Defined in GHC.Num.Singletons

PNum (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PNum (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PNum (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

class SNum a where Source #

Minimal complete definition

(%+), (%*), sAbs, sSignum, sFromInteger

Methods

(%+) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 + t2) infixl 6 Source #

(%-) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 - t2) infixl 6 Source #

default (%-) :: forall (t1 :: a) (t2 :: a). (t1 - t2) ~ TFHelper_6989586621679398594 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 * t2) infixl 7 Source #

sNegate :: forall (t :: a). Sing t -> Sing (Negate t) Source #

default sNegate :: forall (t :: a). Negate t ~ Negate_6989586621679398604 t => Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: a). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: a). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: a) Source #

Instances

Instances details
SNum Natural Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

(%+) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 + t2) Source #

(%-) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 * t2) Source #

sNegate :: forall (t :: Natural). Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: Natural). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: Natural). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: Natural) Source #

SNum a => SNum (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%+) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 + t2) Source #

(%-) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 * t2) Source #

sNegate :: forall (t :: Max a). Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: Max a). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: Max a). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: Max a) Source #

SNum a => SNum (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%+) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 + t2) Source #

(%-) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 * t2) Source #

sNegate :: forall (t :: Min a). Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: Min a). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: Min a). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: Min a) Source #

SNum a => SNum (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

(%+) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 + t2) Source #

(%-) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 * t2) Source #

sNegate :: forall (t :: Identity a). Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: Identity a). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: Identity a). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: Identity a) Source #

SNum a => SNum (Down a) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

(%+) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 + t2) Source #

(%-) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 * t2) Source #

sNegate :: forall (t :: Down a). Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: Down a). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: Down a). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: Down a) Source #

SNum a => SNum (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%+) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 + t2) Source #

(%-) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 * t2) Source #

sNegate :: forall (t :: Product a). Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: Product a). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: Product a). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: Product a) Source #

SNum a => SNum (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%+) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 + t2) Source #

(%-) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 * t2) Source #

sNegate :: forall (t :: Sum a). Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: Sum a). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: Sum a). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: Sum a) Source #

SNum a => SNum (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

(%+) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 + t2) Source #

(%-) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 - t2) Source #

(%*) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 * t2) Source #

sNegate :: forall (t :: Const a b). Sing t -> Sing (Negate t) Source #

sAbs :: forall (t :: Const a b). Sing t -> Sing (Abs t) Source #

sSignum :: forall (t :: Const a b). Sing t -> Sing (Signum t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (FromInteger t :: Const a b) Source #

Numeric functions

type family Subtract (a1 :: a) (a2 :: a) :: a where ... Source #

Equations

Subtract (x :: k2) (y :: k2) = Apply (Apply ((-@#@$) :: TyFun k2 (k2 ~> k2) -> Type) y) x 

sSubtract :: forall a (t1 :: a) (t2 :: a). SNum a => Sing t1 -> Sing t2 -> Sing (Subtract t1 t2) Source #

Semigroups and Monoids

class PSemigroup a Source #

Associated Types

type (arg :: a) <> (arg1 :: a) :: a infixr 6 Source #

Instances

Instances details
PSemigroup Void Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type (a1 :: Void) <> (a2 :: Void) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type (a1 :: Void) <> (a2 :: Void)
type Sconcat (arg :: NonEmpty Void) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Sconcat (arg :: NonEmpty Void)
PSemigroup All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a1 :: All) <> (a2 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: All) <> (a2 :: All)
type Sconcat (arg :: NonEmpty All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sconcat (arg :: NonEmpty All)
PSemigroup Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a1 :: Any) <> (a2 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: Any) <> (a2 :: Any)
type Sconcat (arg :: NonEmpty Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sconcat (arg :: NonEmpty Any)
PSemigroup Ordering Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type (a1 :: Ordering) <> (a2 :: Ordering) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type (a1 :: Ordering) <> (a2 :: Ordering)
type Sconcat (arg :: NonEmpty Ordering) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Sconcat (arg :: NonEmpty Ordering)
PSemigroup () Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type (a1 :: ()) <> (a2 :: ()) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type (a1 :: ()) <> (a2 :: ())
type Sconcat (a :: NonEmpty ()) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Sconcat (a :: NonEmpty ())
PSemigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type (a :: Symbol) <> (b :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (a :: Symbol) <> (b :: Symbol) = AppendSymbol a b
type Sconcat (arg :: NonEmpty Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sconcat (arg :: NonEmpty Symbol)
PSemigroup (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

PSemigroup (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PSemigroup (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

PSemigroup (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PSemigroup (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PSemigroup (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PSemigroup (Maybe a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup [a] Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (Either a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

PSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (a, b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

class SSemigroup a where Source #

Methods

(%<>) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) infixr 6 Source #

Instances

Instances details
SSemigroup Void Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty Void). Sing t -> Sing (Sconcat t) Source #

SSemigroup All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%<>) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty All). Sing t -> Sing (Sconcat t) Source #

SSemigroup Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%<>) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty Any). Sing t -> Sing (Sconcat t) Source #

SSemigroup Ordering Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty Ordering). Sing t -> Sing (Sconcat t) Source #

SSemigroup () Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty ()). Sing t -> Sing (Sconcat t) Source #

SSemigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

(%<>) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty Symbol). Sing t -> Sing (Sconcat t) Source #

SSemigroup (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%<>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Sconcat t) Source #

SSemigroup (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%<>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Sconcat t) Source #

SOrd a => SSemigroup (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%<>) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Max a)). Sing t -> Sing (Sconcat t) Source #

SOrd a => SSemigroup (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%<>) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Min a)). Sing t -> Sing (Sconcat t) Source #

SMonoid m => SSemigroup (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%<>) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (WrappedMonoid m)). Sing t -> Sing (Sconcat t) Source #

SSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Sconcat t) Source #

SSemigroup a => SSemigroup (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

(%<>) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Identity a)). Sing t -> Sing (Sconcat t) Source #

SSemigroup (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

(%<>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Sconcat t) Source #

SSemigroup (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

(%<>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Sconcat t) Source #

SSemigroup a => SSemigroup (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

(%<>) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Down a)). Sing t -> Sing (Sconcat t) Source #

SSemigroup a => SSemigroup (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%<>) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Dual a)). Sing t -> Sing (Sconcat t) Source #

SNum a => SSemigroup (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%<>) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Product a)). Sing t -> Sing (Sconcat t) Source #

SNum a => SSemigroup (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%<>) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Sum a)). Sing t -> Sing (Sconcat t) Source #

SSemigroup a => SSemigroup (Maybe a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Maybe a)). Sing t -> Sing (Sconcat t) Source #

SSemigroup [a] Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty [a]). Sing t -> Sing (Sconcat t) Source #

SSemigroup (Either a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Either a b)). Sing t -> Sing (Sconcat t) Source #

SSemigroup (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

(%<>) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Proxy s)). Sing t -> Sing (Sconcat t) Source #

SSemigroup b => SSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: a ~> b) (t2 :: a ~> b). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (a ~> b)). Sing t -> Sing (Sconcat t) Source #

(SSemigroup a, SSemigroup b) => SSemigroup (a, b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Sconcat t) Source #

SSemigroup a => SSemigroup (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

(%<>) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (Const a b)). Sing t -> Sing (Sconcat t) Source #

(SSemigroup a, SSemigroup b, SSemigroup c) => SSemigroup (a, b, c) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c)). Sing t -> Sing (Sconcat t) Source #

(SSemigroup a, SSemigroup b, SSemigroup c, SSemigroup d) => SSemigroup (a, b, c, d) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c, d)). Sing t -> Sing (Sconcat t) Source #

(SSemigroup a, SSemigroup b, SSemigroup c, SSemigroup d, SSemigroup e) => SSemigroup (a, b, c, d, e) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (t1 <> t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c, d, e)). Sing t -> Sing (Sconcat t) Source #

class PMonoid a Source #

Associated Types

type Mempty :: a Source #

type Mappend (arg :: a) (arg1 :: a) :: a Source #

type Mappend (arg :: a) (arg1 :: a) = Mappend_6989586621679860753 arg arg1

type Mconcat (arg :: [a]) :: a Source #

type Mconcat (arg :: [a]) = Mconcat_6989586621679860767 arg

Instances

Instances details
PMonoid All Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
type Mappend (arg1 :: All) (arg2 :: All) 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: All) (arg2 :: All)
type Mconcat (arg :: [All]) 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (arg :: [All])
PMonoid Any Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
type Mappend (arg1 :: Any) (arg2 :: Any) 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: Any) (arg2 :: Any)
type Mconcat (arg :: [Any]) 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (arg :: [Any])
PMonoid Ordering Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
type Mappend (arg1 :: Ordering) (arg2 :: Ordering) 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: Ordering) (arg2 :: Ordering)
type Mconcat (arg :: [Ordering]) 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (arg :: [Ordering])
PMonoid () Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
type Mappend (arg1 :: ()) (arg2 :: ()) 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: ()) (arg2 :: ())
type Mconcat (a :: [()]) 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (a :: [()])
PMonoid Symbol Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
type Mappend (arg1 :: Symbol) (arg2 :: Symbol) 
Instance details

Defined in Data.Monoid.Singletons

type Mappend (arg1 :: Symbol) (arg2 :: Symbol)
type Mconcat (arg :: [Symbol]) 
Instance details

Defined in Data.Monoid.Singletons

type Mconcat (arg :: [Symbol])
PMonoid (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Semigroup.Singletons

type Mempty
PMonoid (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Semigroup.Singletons

type Mempty
PMonoid (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Semigroup.Singletons

type Mempty
PMonoid (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Functor.Identity.Singletons

type Mempty
PMonoid (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (Down a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (Maybe a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid [a] Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Proxy.Singletons

type Mempty
PMonoid (a ~> b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Functor.Const.Singletons

type Mempty
PMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty
PMonoid (a, b, c, d, e) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty 
Instance details

Defined in Data.Monoid.Singletons

type Mempty

class SSemigroup a => SMonoid a where Source #

Minimal complete definition

sMempty

Methods

sMempty :: Sing (Mempty :: a) Source #

sMappend :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

default sMappend :: forall (t1 :: a) (t2 :: a). Mappend t1 t2 ~ Mappend_6989586621679860753 t1 t2 => Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [a]). Sing t -> Sing (Mconcat t) Source #

default sMconcat :: forall (t :: [a]). Mconcat t ~ Mconcat_6989586621679860767 t => Sing t -> Sing (Mconcat t) Source #

Instances

Instances details
SMonoid All Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: All) Source #

sMappend :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [All]). Sing t -> Sing (Mconcat t) Source #

SMonoid Any Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Any) Source #

sMappend :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Any]). Sing t -> Sing (Mconcat t) Source #

SMonoid Ordering Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Ordering) Source #

sMappend :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Ordering]). Sing t -> Sing (Mconcat t) Source #

SMonoid () Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: ()) Source #

sMappend :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [()]). Sing t -> Sing (Mconcat t) Source #

SMonoid Symbol Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Symbol) Source #

sMappend :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Symbol]). Sing t -> Sing (Mconcat t) Source #

(SOrd a, SBounded a) => SMonoid (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sMempty :: Sing (Mempty :: Max a) Source #

sMappend :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Max a]). Sing t -> Sing (Mconcat t) Source #

(SOrd a, SBounded a) => SMonoid (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sMempty :: Sing (Mempty :: Min a) Source #

sMappend :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Min a]). Sing t -> Sing (Mconcat t) Source #

SMonoid m => SMonoid (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sMempty :: Sing (Mempty :: WrappedMonoid m) Source #

sMappend :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [WrappedMonoid m]). Sing t -> Sing (Mconcat t) Source #

SMonoid a => SMonoid (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sMempty :: Sing (Mempty :: Identity a) Source #

sMappend :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Identity a]). Sing t -> Sing (Mconcat t) Source #

SMonoid (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: First a) Source #

sMappend :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [First a]). Sing t -> Sing (Mconcat t) Source #

SMonoid (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Last a) Source #

sMappend :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Last a]). Sing t -> Sing (Mconcat t) Source #

SMonoid a => SMonoid (Down a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Down a) Source #

sMappend :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Down a]). Sing t -> Sing (Mconcat t) Source #

SMonoid a => SMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Dual a) Source #

sMappend :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Dual a]). Sing t -> Sing (Mconcat t) Source #

SNum a => SMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Product a) Source #

sMappend :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Product a]). Sing t -> Sing (Mconcat t) Source #

SNum a => SMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Sum a) Source #

sMappend :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Sum a]). Sing t -> Sing (Mconcat t) Source #

SSemigroup a => SMonoid (Maybe a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: Maybe a) Source #

sMappend :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Maybe a]). Sing t -> Sing (Mconcat t) Source #

SMonoid [a] Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: [a]) Source #

sMappend :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [[a]]). Sing t -> Sing (Mconcat t) Source #

SMonoid (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sMempty :: Sing (Mempty :: Proxy s) Source #

sMappend :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Proxy s]). Sing t -> Sing (Mconcat t) Source #

SMonoid b => SMonoid (a ~> b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: a ~> b) Source #

sMappend :: forall (t1 :: a ~> b) (t2 :: a ~> b). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [a ~> b]). Sing t -> Sing (Mconcat t) Source #

(SMonoid a, SMonoid b) => SMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: (a, b)) Source #

sMappend :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [(a, b)]). Sing t -> Sing (Mconcat t) Source #

SMonoid a => SMonoid (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sMempty :: Sing (Mempty :: Const a b) Source #

sMappend :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [Const a b]). Sing t -> Sing (Mconcat t) Source #

(SMonoid a, SMonoid b, SMonoid c) => SMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: (a, b, c)) Source #

sMappend :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [(a, b, c)]). Sing t -> Sing (Mconcat t) Source #

(SMonoid a, SMonoid b, SMonoid c, SMonoid d) => SMonoid (a, b, c, d) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: (a, b, c, d)) Source #

sMappend :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [(a, b, c, d)]). Sing t -> Sing (Mconcat t) Source #

(SMonoid a, SMonoid b, SMonoid c, SMonoid d, SMonoid e) => SMonoid (a, b, c, d, e) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (Mempty :: (a, b, c, d, e)) Source #

sMappend :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Mappend t1 t2) Source #

sMconcat :: forall (t :: [(a, b, c, d, e)]). Sing t -> Sing (Mconcat t) Source #

Monads and functors

class PFunctor (f :: Type -> Type) Source #

Associated Types

type Fmap (arg :: a ~> b) (arg1 :: f a) :: f b Source #

type (arg :: a) <$ (arg1 :: f b) :: f a infixl 4 Source #

type (arg :: a) <$ (arg1 :: f b) = TFHelper_6989586621679271236 arg arg1

Instances

Instances details
PFunctor First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: First a1)
type (a2 :: a1) <$ (a3 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: a1) <$ (a3 :: First b)
PFunctor Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1)
type (a2 :: a1) <$ (a3 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: a1) <$ (a3 :: Last b)
PFunctor Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Max a1)
type (a2 :: a1) <$ (a3 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: a1) <$ (a3 :: Max b)
PFunctor Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Min a1)
type (a2 :: a1) <$ (a3 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: a1) <$ (a3 :: Min b)
PFunctor NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: NonEmpty a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Fmap (a2 :: a1 ~> b) (a3 :: NonEmpty a1)
type (a2 :: a1) <$ (a3 :: NonEmpty b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: a1) <$ (a3 :: NonEmpty b)
PFunctor Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Identity a1)
type (a2 :: a1) <$ (a3 :: Identity b) 
Instance details

Defined in Data.Functor.Identity.Singletons

type (a2 :: a1) <$ (a3 :: Identity b)
PFunctor First Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: First a1) 
Instance details

Defined in Data.Monoid.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: First a1)
type (a2 :: a1) <$ (a3 :: First b) 
Instance details

Defined in Data.Monoid.Singletons

type (a2 :: a1) <$ (a3 :: First b)
PFunctor Last Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1) 
Instance details

Defined in Data.Monoid.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1)
type (a2 :: a1) <$ (a3 :: Last b) 
Instance details

Defined in Data.Monoid.Singletons

type (a2 :: a1) <$ (a3 :: Last b)
PFunctor Down Source # 
Instance details

Defined in Data.Functor.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Down a1) 
Instance details

Defined in Data.Functor.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Down a1)
type (a2 :: a1) <$ (a3 :: Down b) 
Instance details

Defined in Data.Functor.Singletons

type (a2 :: a1) <$ (a3 :: Down b)
PFunctor Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Dual a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Fmap (a2 :: a1 ~> b) (a3 :: Dual a1)
type (a2 :: a1) <$ (a3 :: Dual b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: a1) <$ (a3 :: Dual b)
PFunctor Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Product a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Fmap (a2 :: a1 ~> b) (a3 :: Product a1)
type (a2 :: a1) <$ (a3 :: Product b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: a1) <$ (a3 :: Product b)
PFunctor Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Sum a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Fmap (a2 :: a1 ~> b) (a3 :: Sum a1)
type (a2 :: a1) <$ (a3 :: Sum b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: a1) <$ (a3 :: Sum b)
PFunctor Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Maybe a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Fmap (a2 :: a1 ~> b) (a3 :: Maybe a1)
type (a2 :: a1) <$ (a3 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: a1) <$ (a3 :: Maybe b)
PFunctor [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: [a1]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Fmap (a2 :: a1 ~> b) (a3 :: [a1])
type (a2 :: a1) <$ (a3 :: [b]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: a1) <$ (a3 :: [b])
PFunctor (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PFunctor (Either a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

PFunctor (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1) 
Instance details

Defined in Data.Proxy.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Proxy a1)
type (arg :: a) <$ (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: a) <$ (arg1 :: Proxy b)
PFunctor ((,) a) Source # 
Instance details

Defined in Data.Functor.Singletons

PFunctor (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

PFunctor (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

PFunctor (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

PFunctor (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

class SFunctor (f :: Type -> Type) where Source #

Minimal complete definition

sFmap

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: f a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: f b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) infixl 4 Source #

default (%<$) :: forall a b (t1 :: a) (t2 :: f b). (t1 <$ t2) ~ TFHelper_6989586621679271236 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

Instances

Instances details
SFunctor First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor First Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Last Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Down Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFmap :: forall a0 b (t1 :: a0 ~> b) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor (Either a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sFmap :: forall a0 b (t1 :: a0 ~> b) (t2 :: Either a a0). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor ((,) a) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sFmap :: forall a0 b (t1 :: a0 ~> b) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

SFunctor (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Const m b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

(SFunctor f, SFunctor g) => SFunctor (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

(SFunctor f, SFunctor g) => SFunctor (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Sum f g b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

(SFunctor f, SFunctor g) => SFunctor (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Fmap t1 t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Compose f g b). Sing t1 -> Sing t2 -> Sing (t1 <$ t2) Source #

type family (a1 :: a ~> b) <$> (a2 :: f a) :: f b where ... infixl 4 Source #

Equations

(a_6989586621679357513 :: a ~> b) <$> (a_6989586621679357515 :: f a) = Apply (Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) a_6989586621679357513) a_6989586621679357515 

(%<$>) :: forall a b (f :: Type -> Type) (t1 :: a ~> b) (t2 :: f a). SFunctor f => Sing t1 -> Sing t2 -> Sing (t1 <$> t2) infixl 4 Source #

class PApplicative (f :: Type -> Type) Source #

Associated Types

type Pure (arg :: a) :: f a Source #

type (arg :: f (a ~> b)) <*> (arg1 :: f a) :: f b infixl 4 Source #

type (arg :: f (a ~> b)) <*> (arg1 :: f a) = TFHelper_6989586621679271276 arg arg1

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: f a) (arg2 :: f b) :: f c Source #

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: f a) (arg2 :: f b) = LiftA2_6989586621679271292 arg arg1 arg2

type (arg :: f a) *> (arg1 :: f b) :: f b infixl 4 Source #

type (arg :: f a) *> (arg1 :: f b) = TFHelper_6989586621679271308 arg arg1

type (arg :: f a) <* (arg1 :: f b) :: f a infixl 4 Source #

type (arg :: f a) <* (arg1 :: f b) = TFHelper_6989586621679271319 arg arg1

Instances

Instances details
PApplicative First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a2 :: a1)
type (a2 :: First (a1 ~> b)) <*> (a3 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: First (a1 ~> b)) <*> (a3 :: First a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: First a1) (a4 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: First a1) (a4 :: First b)
type (a2 :: First a1) *> (a3 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: First a1) *> (a3 :: First b)
type (a2 :: First a1) <* (a3 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: First a1) <* (a3 :: First b)
PApplicative Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a2 :: a1)
type (a2 :: Last (a1 ~> b)) <*> (a3 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Last (a1 ~> b)) <*> (a3 :: Last a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Last a1) (a4 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Last a1) (a4 :: Last b)
type (a2 :: Last a1) *> (a3 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Last a1) *> (a3 :: Last b)
type (a2 :: Last a1) <* (a3 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Last a1) <* (a3 :: Last b)
PApplicative Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a2 :: a1)
type (a2 :: Max (a1 ~> b)) <*> (a3 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Max (a1 ~> b)) <*> (a3 :: Max a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Max a1) (a4 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Max a1) (a4 :: Max b)
type (a2 :: Max a1) *> (a3 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Max a1) *> (a3 :: Max b)
type (a2 :: Max a1) <* (a3 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Max a1) <* (a3 :: Max b)
PApplicative Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a2 :: a1)
type (a2 :: Min (a1 ~> b)) <*> (a3 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Min (a1 ~> b)) <*> (a3 :: Min a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Min a1) (a4 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Min a1) (a4 :: Min b)
type (a2 :: Min a1) *> (a3 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Min a1) *> (a3 :: Min b)
type (a2 :: Min a1) <* (a3 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Min a1) <* (a3 :: Min b)
PApplicative NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Pure (a2 :: a1)
type (a2 :: NonEmpty (a1 ~> b)) <*> (a3 :: NonEmpty a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: NonEmpty (a1 ~> b)) <*> (a3 :: NonEmpty a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: NonEmpty a1) (a4 :: NonEmpty b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: NonEmpty a1) (a4 :: NonEmpty b)
type (arg1 :: NonEmpty a) *> (arg2 :: NonEmpty b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (arg1 :: NonEmpty a) *> (arg2 :: NonEmpty b)
type (arg1 :: NonEmpty a) <* (arg2 :: NonEmpty b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (arg1 :: NonEmpty a) <* (arg2 :: NonEmpty b)
PApplicative Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Pure (a2 :: a1)
type (a2 :: Identity (a1 ~> b)) <*> (a3 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type (a2 :: Identity (a1 ~> b)) <*> (a3 :: Identity a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Identity a1) (a4 :: Identity b) 
Instance details

Defined in Data.Functor.Identity.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Identity a1) (a4 :: Identity b)
type (arg :: Identity a) *> (arg1 :: Identity b) 
Instance details

Defined in Data.Functor.Identity.Singletons

type (arg :: Identity a) *> (arg1 :: Identity b)
type (arg :: Identity a) <* (arg1 :: Identity b) 
Instance details

Defined in Data.Functor.Identity.Singletons

type (arg :: Identity a) <* (arg1 :: Identity b)
PApplicative First Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Monoid.Singletons

type Pure (a2 :: a1)
type (a2 :: First (a1 ~> b)) <*> (a3 :: First a1) 
Instance details

Defined in Data.Monoid.Singletons

type (a2 :: First (a1 ~> b)) <*> (a3 :: First a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: First a) (arg2 :: First b) 
Instance details

Defined in Data.Monoid.Singletons

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: First a) (arg2 :: First b)
type (arg :: First a) *> (arg1 :: First b) 
Instance details

Defined in Data.Monoid.Singletons

type (arg :: First a) *> (arg1 :: First b)
type (arg :: First a) <* (arg1 :: First b) 
Instance details

Defined in Data.Monoid.Singletons

type (arg :: First a) <* (arg1 :: First b)
PApplicative Last Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Monoid.Singletons

type Pure (a2 :: a1)
type (a2 :: Last (a1 ~> b)) <*> (a3 :: Last a1) 
Instance details

Defined in Data.Monoid.Singletons

type (a2 :: Last (a1 ~> b)) <*> (a3 :: Last a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Last a) (arg2 :: Last b) 
Instance details

Defined in Data.Monoid.Singletons

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Last a) (arg2 :: Last b)
type (arg :: Last a) *> (arg1 :: Last b) 
Instance details

Defined in Data.Monoid.Singletons

type (arg :: Last a) *> (arg1 :: Last b)
type (arg :: Last a) <* (arg1 :: Last b) 
Instance details

Defined in Data.Monoid.Singletons

type (arg :: Last a) <* (arg1 :: Last b)
PApplicative Down Source # 
Instance details

Defined in Control.Applicative.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Control.Applicative.Singletons

type Pure (a2 :: a1)
type (a2 :: Down (a1 ~> b)) <*> (a3 :: Down a1) 
Instance details

Defined in Control.Applicative.Singletons

type (a2 :: Down (a1 ~> b)) <*> (a3 :: Down a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Down a) (arg2 :: Down b) 
Instance details

Defined in Control.Applicative.Singletons

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Down a) (arg2 :: Down b)
type (arg :: Down a) *> (arg1 :: Down b) 
Instance details

Defined in Control.Applicative.Singletons

type (arg :: Down a) *> (arg1 :: Down b)
type (arg :: Down a) <* (arg1 :: Down b) 
Instance details

Defined in Control.Applicative.Singletons

type (arg :: Down a) <* (arg1 :: Down b)
PApplicative Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Pure (a2 :: a1)
type (a2 :: Dual (a1 ~> b)) <*> (a3 :: Dual a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: Dual (a1 ~> b)) <*> (a3 :: Dual a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Dual a) (arg2 :: Dual b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Dual a) (arg2 :: Dual b)
type (arg :: Dual a) *> (arg1 :: Dual b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Dual a) *> (arg1 :: Dual b)
type (arg :: Dual a) <* (arg1 :: Dual b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Dual a) <* (arg1 :: Dual b)
PApplicative Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Pure (a2 :: a1)
type (a2 :: Product (a1 ~> b)) <*> (a3 :: Product a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: Product (a1 ~> b)) <*> (a3 :: Product a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Product a) (arg2 :: Product b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Product a) (arg2 :: Product b)
type (arg :: Product a) *> (arg1 :: Product b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Product a) *> (arg1 :: Product b)
type (arg :: Product a) <* (arg1 :: Product b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Product a) <* (arg1 :: Product b)
PApplicative Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Pure (a2 :: a1)
type (a2 :: Sum (a1 ~> b)) <*> (a3 :: Sum a1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: Sum (a1 ~> b)) <*> (a3 :: Sum a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Sum a) (arg2 :: Sum b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Sum a) (arg2 :: Sum b)
type (arg :: Sum a) *> (arg1 :: Sum b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Sum a) *> (arg1 :: Sum b)
type (arg :: Sum a) <* (arg1 :: Sum b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Sum a) <* (arg1 :: Sum b)
PApplicative Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Pure (a2 :: a1)
type (a2 :: Maybe (a1 ~> b)) <*> (a3 :: Maybe a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe (a1 ~> b)) <*> (a3 :: Maybe a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Maybe a1) (a4 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Maybe a1) (a4 :: Maybe b)
type (a2 :: Maybe a1) *> (a3 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe a1) *> (a3 :: Maybe b)
type (arg1 :: Maybe a) <* (arg2 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (arg1 :: Maybe a) <* (arg2 :: Maybe b)
PApplicative [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Pure (a2 :: a1)
type (a2 :: [a1 ~> b]) <*> (a3 :: [a1]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: [a1 ~> b]) <*> (a3 :: [a1])
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: [a1]) (a4 :: [b]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: [a1]) (a4 :: [b])
type (a2 :: [a1]) *> (a3 :: [b]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: [a1]) *> (a3 :: [b])
type (arg1 :: [a]) <* (arg2 :: [b]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (arg1 :: [a]) <* (arg2 :: [b])
PApplicative (Either e) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

PApplicative (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Pure (a2 :: a1) 
Instance details

Defined in Data.Proxy.Singletons

type Pure (a2 :: a1)
type (a2 :: Proxy (a1 ~> b)) <*> (a3 :: Proxy a1) 
Instance details

Defined in Data.Proxy.Singletons

type (a2 :: Proxy (a1 ~> b)) <*> (a3 :: Proxy a1)
type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Proxy a) (arg2 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type LiftA2 (arg :: a ~> (b ~> c)) (arg1 :: Proxy a) (arg2 :: Proxy b)
type (arg :: Proxy a) *> (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) *> (arg1 :: Proxy b)
type (arg :: Proxy a) <* (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) <* (arg1 :: Proxy b)
PApplicative ((,) a) Source # 
Instance details

Defined in Control.Applicative.Singletons

PApplicative (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

PApplicative (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

PApplicative (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

class SFunctor f => SApplicative (f :: Type -> Type) where Source #

Minimal complete definition

sPure

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: f a) Source #

(%<*>) :: forall a b (t1 :: f (a ~> b)) (t2 :: f a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) infixl 4 Source #

default (%<*>) :: forall a b (t1 :: f (a ~> b)) (t2 :: f a). (t1 <*> t2) ~ TFHelper_6989586621679271276 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: f a) (t3 :: f b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

default sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: f a) (t3 :: f b). LiftA2 t1 t2 t3 ~ LiftA2_6989586621679271292 t1 t2 t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: f a) (t2 :: f b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) infixl 4 Source #

default (%*>) :: forall a b (t1 :: f a) (t2 :: f b). (t1 *> t2) ~ TFHelper_6989586621679271308 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: f a) (t2 :: f b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) infixl 4 Source #

default (%<*) :: forall a b (t1 :: f a) (t2 :: f b). (t1 <* t2) ~ TFHelper_6989586621679271319 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

Instances

Instances details
SApplicative First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: First a) Source #

(%<*>) :: forall a b (t1 :: First (a ~> b)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: First a) (t3 :: First b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Last a) Source #

(%<*>) :: forall a b (t1 :: Last (a ~> b)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Last a) (t3 :: Last b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Max a) Source #

(%<*>) :: forall a b (t1 :: Max (a ~> b)) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Max a) (t3 :: Max b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Max a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Max a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Min a) Source #

(%<*>) :: forall a b (t1 :: Min (a ~> b)) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Min a) (t3 :: Min b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Min a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Min a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: NonEmpty a) Source #

(%<*>) :: forall a b (t1 :: NonEmpty (a ~> b)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: NonEmpty a) (t3 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Identity a) Source #

(%<*>) :: forall a b (t1 :: Identity (a ~> b)) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Identity a) (t3 :: Identity b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Identity a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Identity a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative First Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: First a) Source #

(%<*>) :: forall a b (t1 :: First (a ~> b)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: First a) (t3 :: First b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Last Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Last a) Source #

(%<*>) :: forall a b (t1 :: Last (a ~> b)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Last a) (t3 :: Last b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Down Source # 
Instance details

Defined in Control.Applicative.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Down a) Source #

(%<*>) :: forall a b (t1 :: Down (a ~> b)) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Down a) (t3 :: Down b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Down a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Down a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Dual a) Source #

(%<*>) :: forall a b (t1 :: Dual (a ~> b)) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Dual a) (t3 :: Dual b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Dual a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Dual a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Product a) Source #

(%<*>) :: forall a b (t1 :: Product (a ~> b)) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Product a) (t3 :: Product b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Product a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Product a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Sum a) Source #

(%<*>) :: forall a b (t1 :: Sum (a ~> b)) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Sum a) (t3 :: Sum b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Sum a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Sum a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Maybe a) Source #

(%<*>) :: forall a b (t1 :: Maybe (a ~> b)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Maybe a) (t3 :: Maybe b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: [a]) Source #

(%<*>) :: forall a b (t1 :: [a ~> b]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: [a]) (t3 :: [b]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative (Either e) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Either e a) Source #

(%<*>) :: forall a b (t1 :: Either e (a ~> b)) (t2 :: Either e a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Either e a) (t3 :: Either e b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Either e a) (t2 :: Either e b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Either e a) (t2 :: Either e b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SApplicative (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Proxy a) Source #

(%<*>) :: forall a b (t1 :: Proxy (a ~> b)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Proxy a) (t3 :: Proxy b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SMonoid a => SApplicative ((,) a) Source # 
Instance details

Defined in Control.Applicative.Singletons

Methods

sPure :: forall a0 (t :: a0). Sing t -> Sing (Pure t :: (a, a)) Source #

(%<*>) :: forall a0 b (t1 :: (a, a0 ~> b)) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a0 b c (t1 :: a0 ~> (b ~> c)) (t2 :: (a, a0)) (t3 :: (a, b)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a0 b (t1 :: (a, a0)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a0 b (t1 :: (a, a0)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

SMonoid m => SApplicative (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Const m a) Source #

(%<*>) :: forall a b (t1 :: Const m (a ~> b)) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Const m a) (t3 :: Const m b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Const m a) (t2 :: Const m b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Const m a) (t2 :: Const m b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

(SApplicative f, SApplicative g) => SApplicative (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Product f g a) Source #

(%<*>) :: forall a b (t1 :: Product f g (a ~> b)) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Product f g a) (t3 :: Product f g b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Product f g a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Product f g a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

(SApplicative f, SApplicative g) => SApplicative (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Pure t :: Compose f g a) Source #

(%<*>) :: forall a b (t1 :: Compose f g (a ~> b)) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (t1 <*> t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Compose f g a) (t3 :: Compose f g b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (LiftA2 t1 t2 t3) Source #

(%*>) :: forall a b (t1 :: Compose f g a) (t2 :: Compose f g b). Sing t1 -> Sing t2 -> Sing (t1 *> t2) Source #

(%<*) :: forall a b (t1 :: Compose f g a) (t2 :: Compose f g b). Sing t1 -> Sing t2 -> Sing (t1 <* t2) Source #

class PMonad (m :: Type -> Type) Source #

Associated Types

type (arg :: m a) >>= (arg1 :: a ~> m b) :: m b infixl 1 Source #

type (arg :: m a) >> (arg1 :: m b) :: m b infixl 1 Source #

type (arg :: m a) >> (arg1 :: m b) = TFHelper_6989586621679271347 arg arg1

type Return (arg :: a) :: m a Source #

type Return (arg :: a) = Return_6989586621679271362 arg :: m a

Instances

Instances details
PMonad First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type (a2 :: First a1) >>= (a3 :: a1 ~> First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: First a1) >>= (a3 :: a1 ~> First b)
type (a2 :: First a1) >> (a3 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: First a1) >> (a3 :: First b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons

type Return (arg :: a)
PMonad Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type (a2 :: Last a1) >>= (a3 :: a1 ~> Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Last a1) >>= (a3 :: a1 ~> Last b)
type (a2 :: Last a1) >> (a3 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Last a1) >> (a3 :: Last b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons

type Return (arg :: a)
PMonad Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type (a2 :: Max a1) >>= (a3 :: a1 ~> Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Max a1) >>= (a3 :: a1 ~> Max b)
type (a2 :: Max a1) >> (a3 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Max a1) >> (a3 :: Max b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons

type Return (arg :: a)
PMonad Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type (a2 :: Min a1) >>= (a3 :: a1 ~> Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Min a1) >>= (a3 :: a1 ~> Min b)
type (a2 :: Min a1) >> (a3 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Min a1) >> (a3 :: Min b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons

type Return (arg :: a)
PMonad NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type (a2 :: NonEmpty a1) >>= (a3 :: a1 ~> NonEmpty b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: NonEmpty a1) >>= (a3 :: a1 ~> NonEmpty b)
type (arg1 :: NonEmpty a) >> (arg2 :: NonEmpty b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (arg1 :: NonEmpty a) >> (arg2 :: NonEmpty b)
type Return (arg :: a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Return (arg :: a)
PMonad Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type (a2 :: Identity a1) >>= (a3 :: a1 ~> Identity b) 
Instance details

Defined in Data.Functor.Identity.Singletons

type (a2 :: Identity a1) >>= (a3 :: a1 ~> Identity b)
type (arg :: Identity a) >> (arg1 :: Identity b) 
Instance details

Defined in Data.Functor.Identity.Singletons

type (arg :: Identity a) >> (arg1 :: Identity b)
type Return (arg :: a) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Return (arg :: a)
PMonad First Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type (a2 :: First a1) >>= (a3 :: a1 ~> First b) 
Instance details

Defined in Data.Monoid.Singletons

type (a2 :: First a1) >>= (a3 :: a1 ~> First b)
type (arg :: First a) >> (arg1 :: First b) 
Instance details

Defined in Data.Monoid.Singletons

type (arg :: First a) >> (arg1 :: First b)
type Return (arg :: a) 
Instance details

Defined in Data.Monoid.Singletons

type Return (arg :: a)
PMonad Last Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type (a2 :: Last a1) >>= (a3 :: a1 ~> Last b) 
Instance details

Defined in Data.Monoid.Singletons

type (a2 :: Last a1) >>= (a3 :: a1 ~> Last b)
type (arg :: Last a) >> (arg1 :: Last b) 
Instance details

Defined in Data.Monoid.Singletons

type (arg :: Last a) >> (arg1 :: Last b)
type Return (arg :: a) 
Instance details

Defined in Data.Monoid.Singletons

type Return (arg :: a)
PMonad Down Source # 
Instance details

Defined in Control.Monad.Singletons

Associated Types

type (a2 :: Down a1) >>= (a3 :: a1 ~> Down b) 
Instance details

Defined in Control.Monad.Singletons

type (a2 :: Down a1) >>= (a3 :: a1 ~> Down b)
type (arg :: Down a) >> (arg1 :: Down b) 
Instance details

Defined in Control.Monad.Singletons

type (arg :: Down a) >> (arg1 :: Down b)
type Return (arg :: a) 
Instance details

Defined in Control.Monad.Singletons

type Return (arg :: a)
PMonad Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a2 :: Dual a1) >>= (a3 :: a1 ~> Dual b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: Dual a1) >>= (a3 :: a1 ~> Dual b)
type (arg :: Dual a) >> (arg1 :: Dual b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Dual a) >> (arg1 :: Dual b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Return (arg :: a)
PMonad Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a2 :: Product a1) >>= (a3 :: a1 ~> Product b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: Product a1) >>= (a3 :: a1 ~> Product b)
type (arg :: Product a) >> (arg1 :: Product b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Product a) >> (arg1 :: Product b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Return (arg :: a)
PMonad Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a2 :: Sum a1) >>= (a3 :: a1 ~> Sum b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a2 :: Sum a1) >>= (a3 :: a1 ~> Sum b)
type (arg :: Sum a) >> (arg1 :: Sum b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (arg :: Sum a) >> (arg1 :: Sum b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Return (arg :: a)
PMonad Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type (a2 :: Maybe a1) >>= (a3 :: a1 ~> Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe a1) >>= (a3 :: a1 ~> Maybe b)
type (a2 :: Maybe a1) >> (a3 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: Maybe a1) >> (a3 :: Maybe b)
type Return (arg :: a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Return (arg :: a)
PMonad [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type (a2 :: [a1]) >>= (a3 :: a1 ~> [b]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a2 :: [a1]) >>= (a3 :: a1 ~> [b])
type (arg1 :: [a]) >> (arg2 :: [b]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (arg1 :: [a]) >> (arg2 :: [b])
type Return (arg :: a) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Return (arg :: a)
PMonad (Either e) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

PMonad (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type (a2 :: Proxy a1) >>= (a3 :: a1 ~> Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (a2 :: Proxy a1) >>= (a3 :: a1 ~> Proxy b)
type (arg :: Proxy a) >> (arg1 :: Proxy b) 
Instance details

Defined in Data.Proxy.Singletons

type (arg :: Proxy a) >> (arg1 :: Proxy b)
type Return (arg :: a) 
Instance details

Defined in Data.Proxy.Singletons

type Return (arg :: a)
PMonad ((,) a) Source # 
Instance details

Defined in Control.Monad.Singletons

PMonad (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

class SApplicative m => SMonad (m :: Type -> Type) where Source #

Minimal complete definition

(%>>=)

Methods

(%>>=) :: forall a b (t1 :: m a) (t2 :: a ~> m b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) infixl 1 Source #

(%>>) :: forall a b (t1 :: m a) (t2 :: m b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) infixl 1 Source #

default (%>>) :: forall a b (t1 :: m a) (t2 :: m b). (t1 >> t2) ~ TFHelper_6989586621679271347 t1 t2 => Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: m a) Source #

default sReturn :: forall a (t :: a). (Return t :: m a) ~ (Return_6989586621679271362 t :: m a) => Sing t -> Sing (Return t :: m a) Source #

Instances

Instances details
SMonad First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%>>=) :: forall a b (t1 :: First a) (t2 :: a ~> First b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: First a) Source #

SMonad Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%>>=) :: forall a b (t1 :: Last a) (t2 :: a ~> Last b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Last a) Source #

SMonad Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%>>=) :: forall a b (t1 :: Max a) (t2 :: a ~> Max b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Max a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Max a) Source #

SMonad Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(%>>=) :: forall a b (t1 :: Min a) (t2 :: a ~> Min b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Min a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Min a) Source #

SMonad NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

(%>>=) :: forall a b (t1 :: NonEmpty a) (t2 :: a ~> NonEmpty b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: NonEmpty a) Source #

SMonad Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

(%>>=) :: forall a b (t1 :: Identity a) (t2 :: a ~> Identity b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Identity a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Identity a) Source #

SMonad First Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

(%>>=) :: forall a b (t1 :: First a) (t2 :: a ~> First b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: First a) Source #

SMonad Last Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

(%>>=) :: forall a b (t1 :: Last a) (t2 :: a ~> Last b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Last a) Source #

SMonad Down Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

(%>>=) :: forall a b (t1 :: Down a) (t2 :: a ~> Down b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Down a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Down a) Source #

SMonad Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%>>=) :: forall a b (t1 :: Dual a) (t2 :: a ~> Dual b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Dual a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Dual a) Source #

SMonad Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%>>=) :: forall a b (t1 :: Product a) (t2 :: a ~> Product b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Product a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Product a) Source #

SMonad Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%>>=) :: forall a b (t1 :: Sum a) (t2 :: a ~> Sum b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Sum a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Sum a) Source #

SMonad Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

(%>>=) :: forall a b (t1 :: Maybe a) (t2 :: a ~> Maybe b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Maybe a) Source #

SMonad [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

(%>>=) :: forall a b (t1 :: [a]) (t2 :: a ~> [b]). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: [a]) Source #

SMonad (Either e) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

(%>>=) :: forall a b (t1 :: Either e a) (t2 :: a ~> Either e b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Either e a) (t2 :: Either e b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Either e a) Source #

SMonad (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

(%>>=) :: forall a b (t1 :: Proxy a) (t2 :: a ~> Proxy b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Proxy a) Source #

SMonoid a => SMonad ((,) a) Source # 
Instance details

Defined in Control.Monad.Singletons

Methods

(%>>=) :: forall a0 b (t1 :: (a, a0)) (t2 :: a0 ~> (a, b)). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a0 b (t1 :: (a, a0)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a0 (t :: a0). Sing t -> Sing (Return t :: (a, a)) Source #

(SMonad f, SMonad g) => SMonad (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

(%>>=) :: forall a b (t1 :: Product f g a) (t2 :: a ~> Product f g b). Sing t1 -> Sing t2 -> Sing (t1 >>= t2) Source #

(%>>) :: forall a b (t1 :: Product f g a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (t1 >> t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Return t :: Product f g a) Source #

class PMonadFail (m :: Type -> Type) Source #

Associated Types

type Fail (arg :: [Char]) :: m a Source #

Instances

Instances details
PMonadFail Maybe Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Associated Types

type Fail a2 
Instance details

Defined in Control.Monad.Fail.Singletons

type Fail a2
PMonadFail [] Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Associated Types

type Fail a2 
Instance details

Defined in Control.Monad.Fail.Singletons

type Fail a2

class SMonad m => SMonadFail (m :: Type -> Type) where Source #

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Fail t :: m a) Source #

Instances

Instances details
SMonadFail Maybe Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Fail t :: Maybe a) Source #

SMonadFail [] Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Fail t :: [a]) Source #

type family MapM_ (a1 :: a ~> m b) (a2 :: t a) :: m () where ... Source #

Equations

MapM_ (f :: a1 ~> m a2) (a_6989586621679922444 :: t a1) = Apply (Apply (Apply (FoldrSym0 :: TyFun (a1 ~> (m () ~> m ())) (m () ~> (t a1 ~> m ())) -> Type) (Apply (Apply ((.@#@$) :: TyFun (m a2 ~> (m () ~> m ())) ((a1 ~> m a2) ~> (a1 ~> (m () ~> m ()))) -> Type) ((>>@#@$) :: TyFun (m a2) (m () ~> m ()) -> Type)) f)) (Apply (ReturnSym0 :: TyFun () (m ()) -> Type) Tuple0Sym0)) a_6989586621679922444 

sMapM_ :: forall a (m :: Type -> Type) b (t1 :: Type -> Type) (t2 :: a ~> m b) (t3 :: t1 a). (SFoldable t1, SMonad m) => Sing t2 -> Sing t3 -> Sing (MapM_ t2 t3) Source #

type family Sequence_ (a1 :: t (m a)) :: m () where ... Source #

Equations

Sequence_ (a_6989586621679922421 :: t (m a)) = Apply (Apply (Apply (FoldrSym0 :: TyFun (m a ~> (m () ~> m ())) (m () ~> (t (m a) ~> m ())) -> Type) ((>>@#@$) :: TyFun (m a) (m () ~> m ()) -> Type)) (Apply (ReturnSym0 :: TyFun () (m ()) -> Type) Tuple0Sym0)) a_6989586621679922421 

sSequence_ :: forall (t1 :: Type -> Type) (m :: Type -> Type) a (t2 :: t1 (m a)). (SFoldable t1, SMonad m) => Sing t2 -> Sing (Sequence_ t2) Source #

type family (a1 :: a ~> m b) =<< (a2 :: m a) :: m b where ... infixr 1 Source #

Equations

(f :: a ~> m b) =<< (x :: m a) = Apply (Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) x) f 

(%=<<) :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: m a). SMonad m => Sing t1 -> Sing t2 -> Sing (t1 =<< t2) infixr 1 Source #

Folds and traversals

class PFoldable (t :: Type -> Type) Source #

Associated Types

type FoldMap (arg :: a ~> m) (arg1 :: t a) :: m Source #

type FoldMap (arg :: a ~> m) (arg1 :: t a) = FoldMap_6989586621679922592 arg arg1

type Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: t a) :: b Source #

type Foldr (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: t a) = Foldr_6989586621679922606 arg arg1 arg2

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: t a) :: b Source #

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: t a) = Foldl_6989586621679922644 arg arg1 arg2

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: t a) :: a Source #

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: t a) = Foldr1_6989586621679922681 arg arg1

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: t a) :: a Source #

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: t a) = Foldl1_6989586621679922704 arg arg1

type Elem (arg :: a) (arg1 :: t a) :: Bool Source #

type Elem (arg :: a) (arg1 :: t a) = Elem_6989586621679922769 arg arg1

type Maximum (arg :: t a) :: a Source #

type Maximum (arg :: t a) = Maximum_6989586621679922783 arg

type Minimum (arg :: t a) :: a Source #

type Minimum (arg :: t a) = Minimum_6989586621679922798 arg

type Sum (arg :: t a) :: a Source #

type Sum (arg :: t a) = Sum_6989586621679922813 arg

type Product (arg :: t a) :: a Source #

type Product (arg :: t a) = Product_6989586621679922822 arg

Instances

Instances details
PFoldable First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold (arg :: First m) 
Instance details

Defined in Data.Semigroup.Singletons

type Fold (arg :: First m)
type FoldMap (a2 :: a1 ~> m) (a3 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: First a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: First a1)
type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: First a)
type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a)
type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a)
type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: First a)
type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: First a)
type ToList (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type ToList (arg :: First a)
type Null (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: First a)
type Length (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: First a)
type Elem (arg :: a) (arg1 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Elem (arg :: a) (arg1 :: First a)
type Maximum (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Maximum (arg :: First a)
type Minimum (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Minimum (arg :: First a)
type Sum (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Sum (arg :: First a)
type Product (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Product (arg :: First a)
PFoldable Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold (arg :: Last m) 
Instance details

Defined in Data.Semigroup.Singletons

type Fold (arg :: Last m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Last a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Last a1)
type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Last a)
type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a)
type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a)
type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Last a)
type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Last a)
type ToList (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type ToList (arg :: Last a)
type Null (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Last a)
type Length (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Last a)
type Elem (arg :: a) (arg1 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Elem (arg :: a) (arg1 :: Last a)
type Maximum (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Maximum (arg :: Last a)
type Minimum (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Minimum (arg :: Last a)
type Sum (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Sum (arg :: Last a)
type Product (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Product (arg :: Last a)
PFoldable Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold (arg :: Max m) 
Instance details

Defined in Data.Semigroup.Singletons

type Fold (arg :: Max m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Max a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Max a1)
type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Max a)
type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a)
type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a)
type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Max a)
type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Max a)
type ToList (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type ToList (arg :: Max a)
type Null (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Max a)
type Length (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Max a)
type Elem (arg :: a) (arg1 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Elem (arg :: a) (arg1 :: Max a)
type Maximum (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Maximum (arg :: Max a)
type Minimum (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Minimum (arg :: Max a)
type Sum (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Sum (arg :: Max a)
type Product (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Product (arg :: Max a)
PFoldable Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold (arg :: Min m) 
Instance details

Defined in Data.Semigroup.Singletons

type Fold (arg :: Min m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Min a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Min a1)
type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Min a)
type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a)
type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a)
type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Min a)
type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Min a)
type ToList (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type ToList (arg :: Min a)
type Null (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Min a)
type Length (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Min a)
type Elem (arg :: a) (arg1 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Elem (arg :: a) (arg1 :: Min a)
type Maximum (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Maximum (arg :: Min a)
type Minimum (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Minimum (arg :: Min a)
type Sum (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Sum (arg :: Min a)
type Product (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Product (arg :: Min a)
PFoldable NonEmpty Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (a :: NonEmpty m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (a :: NonEmpty m)
type FoldMap (a2 :: a1 ~> m) (a3 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: NonEmpty a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: NonEmpty a1)
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: NonEmpty a)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: NonEmpty a1)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: NonEmpty a)
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: NonEmpty a1)
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: NonEmpty a1)
type ToList (a2 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (a2 :: NonEmpty a1)
type Null (arg :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: NonEmpty a)
type Length (arg :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: NonEmpty a)
type Elem (arg1 :: a) (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (arg1 :: a) (arg2 :: NonEmpty a)
type Maximum (arg :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (arg :: NonEmpty a)
type Minimum (arg :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (arg :: NonEmpty a)
type Sum (arg :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (arg :: NonEmpty a)
type Product (arg :: NonEmpty a) 
Instance details

Defined in Data.Foldable.Singletons

type Product (arg :: NonEmpty a)
PFoldable Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Fold (arg :: Identity m) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Fold (arg :: Identity m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Identity a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Identity a1)
type Foldr' (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldr' (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Identity a1)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Identity a1)
type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Identity a1)
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Identity a1)
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Identity a1)
type ToList (a2 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type ToList (a2 :: Identity a1)
type Null (a2 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Null (a2 :: Identity a1)
type Length (a2 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Length (a2 :: Identity a1)
type Elem (a2 :: a1) (a3 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Elem (a2 :: a1) (a3 :: Identity a1)
type Maximum (a2 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Maximum (a2 :: Identity a1)
type Minimum (a2 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Minimum (a2 :: Identity a1)
type Sum (a2 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Sum (a2 :: Identity a1)
type Product (a2 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Product (a2 :: Identity a1)
PFoldable First Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (arg :: First m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (arg :: First m)
type FoldMap (a2 :: a1 ~> m) (a3 :: First a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: First a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: First a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: First a1)
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: First a)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: First a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: First a)
type ToList (arg :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (arg :: First a)
type Null (arg :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: First a)
type Length (arg :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: First a)
type Elem (arg1 :: a) (arg2 :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (arg1 :: a) (arg2 :: First a)
type Maximum (arg :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (arg :: First a)
type Minimum (arg :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (arg :: First a)
type Sum (arg :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (arg :: First a)
type Product (arg :: First a) 
Instance details

Defined in Data.Foldable.Singletons

type Product (arg :: First a)
PFoldable Last Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (arg :: Last m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (arg :: Last m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Last a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Last a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Last a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Last a1)
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Last a)
type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Last a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Last a)
type ToList (arg :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (arg :: Last a)
type Null (arg :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: Last a)
type Length (arg :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: Last a)
type Elem (arg1 :: a) (arg2 :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (arg1 :: a) (arg2 :: Last a)
type Maximum (arg :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (arg :: Last a)
type Minimum (arg :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (arg :: Last a)
type Sum (arg :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (arg :: Last a)
type Product (arg :: Last a) 
Instance details

Defined in Data.Foldable.Singletons

type Product (arg :: Last a)
PFoldable Dual Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (arg :: Dual m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (arg :: Dual m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Dual a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Dual a1)
type Foldr' (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Dual a1)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Dual a1)
type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Dual a1)
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Dual a1)
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Dual a1)
type ToList (a2 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (a2 :: Dual a1)
type Null (a2 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Dual a1)
type Length (a2 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Dual a1)
type Elem (a2 :: a1) (a3 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a2 :: a1) (a3 :: Dual a1)
type Maximum (a2 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (a2 :: Dual a1)
type Minimum (a2 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (a2 :: Dual a1)
type Sum (a2 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a2 :: Dual a1)
type Product (a2 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a2 :: Dual a1)
PFoldable Product Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (arg :: Product m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (arg :: Product m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Product a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Product a1)
type Foldr' (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Product a1)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Product a1)
type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Product a1)
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Product a1)
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Product a1)
type ToList (a2 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (a2 :: Product a1)
type Null (a2 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Product a1)
type Length (a2 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Product a1)
type Elem (a2 :: a1) (a3 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a2 :: a1) (a3 :: Product a1)
type Maximum (a2 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (a2 :: Product a1)
type Minimum (a2 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (a2 :: Product a1)
type Sum (a2 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a2 :: Product a1)
type Product (a2 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a2 :: Product a1)
PFoldable Sum Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (arg :: Sum m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (arg :: Sum m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Sum a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Sum a1)
type Foldr' (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Sum a1)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Sum a1)
type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Sum a1)
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Sum a1)
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Sum a1)
type ToList (a2 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (a2 :: Sum a1)
type Null (a2 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Sum a1)
type Length (a2 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Sum a1)
type Elem (a2 :: a1) (a3 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a2 :: a1) (a3 :: Sum a1)
type Maximum (a2 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (a2 :: Sum a1)
type Minimum (a2 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (a2 :: Sum a1)
type Sum (a2 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a2 :: Sum a1)
type Product (a2 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a2 :: Sum a1)
PFoldable Maybe Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (arg :: Maybe m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (arg :: Maybe m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Maybe a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Maybe a1)
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Maybe a)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Maybe a1)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Maybe a)
type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a)
type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (arg1 :: a ~> (a ~> a)) (arg2 :: Maybe a)
type ToList (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (arg :: Maybe a)
type Null (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: Maybe a)
type Length (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: Maybe a)
type Elem (arg1 :: a) (arg2 :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (arg1 :: a) (arg2 :: Maybe a)
type Maximum (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (arg :: Maybe a)
type Minimum (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (arg :: Maybe a)
type Sum (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (arg :: Maybe a)
type Product (arg :: Maybe a) 
Instance details

Defined in Data.Foldable.Singletons

type Product (arg :: Maybe a)
PFoldable [] Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (arg :: [m]) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (arg :: [m])
type FoldMap (arg1 :: a ~> m) (arg2 :: [a]) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (arg1 :: a ~> m) (arg2 :: [a])
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: [a1])
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: [a]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: [a])
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: [a1])
type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: [a1])
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: [a1])
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: [a1])
type ToList (a2 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (a2 :: [a1])
type Null (a2 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: [a1])
type Length (a2 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: [a1])
type Elem (a2 :: a1) (a3 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a2 :: a1) (a3 :: [a1])
type Maximum (a2 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (a2 :: [a1])
type Minimum (a2 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (a2 :: [a1])
type Sum (a2 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a2 :: [a1])
type Product (a2 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a2 :: [a1])
PFoldable (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PFoldable (Either a) Source # 
Instance details

Defined in Data.Foldable.Singletons

PFoldable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (a :: Proxy m) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (a :: Proxy m)
type FoldMap (a2 :: a1 ~> m) (a3 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> m) (a3 :: Proxy a1)
type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (b ~> b)) (a3 :: b) (a4 :: Proxy a1)
type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (arg1 :: a ~> (b ~> b)) (arg2 :: b) (arg3 :: Proxy a)
type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: b ~> (a1 ~> b)) (a3 :: b) (a4 :: Proxy a1)
type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (arg1 :: b ~> (a ~> b)) (arg2 :: b) (arg3 :: Proxy a)
type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1)
type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a2 :: a1 ~> (a1 ~> a1)) (a3 :: Proxy a1)
type ToList (arg :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type ToList (arg :: Proxy a)
type Null (a2 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Proxy a1)
type Length (a2 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Proxy a1)
type Elem (a2 :: a1) (a3 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a2 :: a1) (a3 :: Proxy a1)
type Maximum (arg :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (arg :: Proxy a)
type Minimum (arg :: Proxy a) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (arg :: Proxy a)
type Sum (a2 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a2 :: Proxy a1)
type Product (a2 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a2 :: Proxy a1)
PFoldable ((,) a) Source # 
Instance details

Defined in Data.Foldable.Singletons

PFoldable (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

PFoldable (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

PFoldable (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

PFoldable (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

class SFoldable (t :: Type -> Type) where Source #

Minimal complete definition

Nothing

Methods

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: t a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

default sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: t a). (FoldMap t1 t2 ~ FoldMap_6989586621679922592 t1 t2, SMonoid m) => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: t a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

default sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: t a). Foldr t1 t2 t3 ~ Foldr_6989586621679922606 t1 t2 t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: t a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

default sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: t a). Foldl t1 t2 t3 ~ Foldl_6989586621679922644 t1 t2 t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

default sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). Foldr1 t1 t2 ~ Foldr1_6989586621679922681 t1 t2 => Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

default sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). Foldl1 t1 t2 ~ Foldl1_6989586621679922704 t1 t2 => Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sElem :: forall a (t1 :: a) (t2 :: t a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

default sElem :: forall a (t1 :: a) (t2 :: t a). (Elem t1 t2 ~ Elem_6989586621679922769 t1 t2, SEq a) => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: t a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

default sMaximum :: forall a (t1 :: t a). (Maximum t1 ~ Maximum_6989586621679922783 t1, SOrd a) => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: t a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

default sMinimum :: forall a (t1 :: t a). (Minimum t1 ~ Minimum_6989586621679922798 t1, SOrd a) => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: t a). SNum a => Sing t1 -> Sing (Sum t1) Source #

default sSum :: forall a (t1 :: t a). (Sum t1 ~ Sum_6989586621679922813 t1, SNum a) => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: t a). SNum a => Sing t1 -> Sing (Product t1) Source #

default sProduct :: forall a (t1 :: t a). (Product t1 ~ Product_6989586621679922822 t1, SNum a) => Sing t1 -> Sing (Product t1) Source #

Instances

Instances details
SFoldable First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: First m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: First a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: First a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: First a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: First a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: First a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: First a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: First a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: Last m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Last a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Last a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Last a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Last a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Last a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Last a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Last a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: Max m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Max a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Max a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Max a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Max a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Max a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Max a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Max a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Max a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Max a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: Min m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Min a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Min a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Min a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Min a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Min a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Min a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Min a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Min a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Min a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable NonEmpty Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: NonEmpty m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: NonEmpty a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: NonEmpty a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: NonEmpty a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: NonEmpty a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: NonEmpty a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: NonEmpty a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sFold :: forall m (t1 :: Identity m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Identity a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Identity a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Identity a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Identity a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Identity a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Identity a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Identity a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Identity a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Identity a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable First Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: First m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: First a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: First a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: First a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: First a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: First a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: First a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: First a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Last Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Last m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Last a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Last a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Last a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Last a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Last a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Last a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Last a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Dual Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Dual m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Dual a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Dual a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Dual a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Dual a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Dual a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Dual a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Dual a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Dual a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Dual a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Dual a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Dual a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Dual a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Dual a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Product Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Product m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Product a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Product a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Product a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Product a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Product a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Product a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Product a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Product a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Product a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Product a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Product a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Product a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Product a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Sum Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Sum m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Sum a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Sum a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Sum a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Sum a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Sum a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Sum a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Sum a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Sum a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Sum a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Sum a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Sum a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Sum a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Sum a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable Maybe Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Maybe m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Maybe a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Maybe a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Maybe a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Maybe a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Maybe a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable [] Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: [m]). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: [a]). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: [a]). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: [a]). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: [a]). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: [a]). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: [a]). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: [a]). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: [a]). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: Arg a m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: Arg a a0). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: Arg a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: Arg a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a0 (t1 :: b ~> (a0 ~> b)) (t2 :: b) (t3 :: Arg a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a0 (t1 :: b ~> (a0 ~> b)) (t2 :: b) (t3 :: Arg a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: Arg a a0). SEq a0 => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a0 (t1 :: Arg a a0). SOrd a0 => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a0 (t1 :: Arg a a0). SOrd a0 => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a0 (t1 :: Arg a a0). SNum a0 => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a0 (t1 :: Arg a a0). SNum a0 => Sing t1 -> Sing (Product t1) Source #

SFoldable (Either a) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Either a m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: Either a a0). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: Either a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: Either a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a0 (t1 :: b ~> (a0 ~> b)) (t2 :: b) (t3 :: Either a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a0 (t1 :: b ~> (a0 ~> b)) (t2 :: b) (t3 :: Either a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Either a a0). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Either a a0). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: Either a a0). SEq a0 => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a0 (t1 :: Either a a0). SOrd a0 => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a0 (t1 :: Either a a0). SOrd a0 => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a0 (t1 :: Either a a0). SNum a0 => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a0 (t1 :: Either a a0). SNum a0 => Sing t1 -> Sing (Product t1) Source #

SFoldable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Proxy m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Proxy a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Proxy a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Proxy a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Proxy a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Proxy a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Product t1) Source #

SFoldable ((,) a) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: (a, m)). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: (a, a0)). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: (a, a0)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: (a, a0)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a0 (t1 :: b ~> (a0 ~> b)) (t2 :: b) (t3 :: (a, a0)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a0 (t1 :: b ~> (a0 ~> b)) (t2 :: b) (t3 :: (a, a0)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: (a, a0)). SEq a0 => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a0 (t1 :: (a, a0)). SOrd a0 => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a0 (t1 :: (a, a0)). SOrd a0 => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a0 (t1 :: (a, a0)). SNum a0 => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a0 (t1 :: (a, a0)). SNum a0 => Sing t1 -> Sing (Product t1) Source #

SFoldable (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sFold :: forall m0 (t1 :: Const m m0). SMonoid m0 => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m0 (t1 :: a ~> m0) (t2 :: Const m a). SMonoid m0 => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Const m a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Const m a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Const m a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Const m a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Const m a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Const m a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Const m a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Const m a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Const m a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Const m a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Const m a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Const m a). SNum a => Sing t1 -> Sing (Product t1) Source #

(SFoldable f, SFoldable g) => SFoldable (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sFold :: forall m (t1 :: Product f g m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Product f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Product f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Product f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Product f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Product f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Product f g a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Product f g a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Product f g a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Product f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Product f g a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Product f g a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Product f g a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Product f g a). SNum a => Sing t1 -> Sing (Product t1) Source #

(SFoldable f, SFoldable g) => SFoldable (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sFold :: forall m (t1 :: Sum f g m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Sum f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Sum f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Sum f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Sum f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Sum f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Sum f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Sum f g a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Sum f g a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Sum f g a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Sum f g a). SNum a => Sing t1 -> Sing (Product t1) Source #

(SFoldable f, SFoldable g) => SFoldable (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sFold :: forall m (t1 :: Compose f g m). SMonoid m => Sing t1 -> Sing (Fold t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Compose f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (FoldMap t1 t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Compose f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr t1 t2 t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Compose f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldr' t1 t2 t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Compose f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl t1 t2 t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Compose f g a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Foldl' t1 t2 t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Foldr1 t1 t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Foldl1 t1 t2) Source #

sToList :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (ToList t1) Source #

sNull :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (Null t1) Source #

sLength :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (Length t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Compose f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Elem t1 t2) Source #

sMaximum :: forall a (t1 :: Compose f g a). SOrd a => Sing t1 -> Sing (Maximum t1) Source #

sMinimum :: forall a (t1 :: Compose f g a). SOrd a => Sing t1 -> Sing (Minimum t1) Source #

sSum :: forall a (t1 :: Compose f g a). SNum a => Sing t1 -> Sing (Sum t1) Source #

sProduct :: forall a (t1 :: Compose f g a). SNum a => Sing t1 -> Sing (Product t1) Source #

class PTraversable (t :: Type -> Type) Source #

Associated Types

type Traverse (arg :: a ~> f b) (arg1 :: t a) :: f (t b) Source #

type Traverse (arg :: a ~> f b) (arg1 :: t a) = Traverse_6989586621680096875 arg arg1

type SequenceA (arg :: t (f a)) :: f (t a) Source #

type SequenceA (arg :: t (f a)) = SequenceA_6989586621680096887 arg

type MapM (arg :: a ~> m b) (arg1 :: t a) :: m (t b) Source #

type MapM (arg :: a ~> m b) (arg1 :: t a) = MapM_6989586621680096897 arg arg1

type Sequence (arg :: t (m a)) :: m (t a) Source #

type Sequence (arg :: t (m a)) = Sequence_6989586621680096911 arg

Instances

Instances details
PTraversable First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: First a1)
type SequenceA (arg :: First (f a)) 
Instance details

Defined in Data.Semigroup.Singletons

type SequenceA (arg :: First (f a))
type MapM (arg :: a ~> m b) (arg1 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type MapM (arg :: a ~> m b) (arg1 :: First a)
type Sequence (arg :: First (m a)) 
Instance details

Defined in Data.Semigroup.Singletons

type Sequence (arg :: First (m a))
PTraversable Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Last a1)
type SequenceA (arg :: Last (f a)) 
Instance details

Defined in Data.Semigroup.Singletons

type SequenceA (arg :: Last (f a))
type MapM (arg :: a ~> m b) (arg1 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type MapM (arg :: a ~> m b) (arg1 :: Last a)
type Sequence (arg :: Last (m a)) 
Instance details

Defined in Data.Semigroup.Singletons

type Sequence (arg :: Last (m a))
PTraversable Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Max a1)
type SequenceA (arg :: Max (f a)) 
Instance details

Defined in Data.Semigroup.Singletons

type SequenceA (arg :: Max (f a))
type MapM (arg :: a ~> m b) (arg1 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type MapM (arg :: a ~> m b) (arg1 :: Max a)
type Sequence (arg :: Max (m a)) 
Instance details

Defined in Data.Semigroup.Singletons

type Sequence (arg :: Max (m a))
PTraversable Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Min a1)
type SequenceA (arg :: Min (f a)) 
Instance details

Defined in Data.Semigroup.Singletons

type SequenceA (arg :: Min (f a))
type MapM (arg :: a ~> m b) (arg1 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type MapM (arg :: a ~> m b) (arg1 :: Min a)
type Sequence (arg :: Min (m a)) 
Instance details

Defined in Data.Semigroup.Singletons

type Sequence (arg :: Min (m a))
PTraversable NonEmpty Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: NonEmpty a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: NonEmpty a1)
type SequenceA (arg :: NonEmpty (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: NonEmpty (f a))
type MapM (arg1 :: a ~> m b) (arg2 :: NonEmpty a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: NonEmpty a)
type Sequence (arg :: NonEmpty (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: NonEmpty (m a))
PTraversable Identity Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Identity a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Identity a1)
type SequenceA (arg :: Identity (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: Identity (f a))
type MapM (arg1 :: a ~> m b) (arg2 :: Identity a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: Identity a)
type Sequence (arg :: Identity (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: Identity (m a))
PTraversable First Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: First a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: First a1)
type SequenceA (arg :: First (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: First (f a))
type MapM (arg1 :: a ~> m b) (arg2 :: First a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: First a)
type Sequence (arg :: First (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: First (m a))
PTraversable Last Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Last a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Last a1)
type SequenceA (arg :: Last (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: Last (f a))
type MapM (arg1 :: a ~> m b) (arg2 :: Last a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: Last a)
type Sequence (arg :: Last (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: Last (m a))
PTraversable Dual Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Dual a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Dual a1)
type SequenceA (arg :: Dual (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: Dual (f a))
type MapM (arg1 :: a ~> m b) (arg2 :: Dual a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: Dual a)
type Sequence (arg :: Dual (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: Dual (m a))
PTraversable Product Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Product a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Product a1)
type SequenceA (arg :: Product (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: Product (f a))
type MapM (arg1 :: a ~> m b) (arg2 :: Product a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: Product a)
type Sequence (arg :: Product (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: Product (m a))
PTraversable Sum Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Sum a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Sum a1)
type SequenceA (arg :: Sum (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: Sum (f a))
type MapM (arg1 :: a ~> m b) (arg2 :: Sum a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: Sum a)
type Sequence (arg :: Sum (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: Sum (m a))
PTraversable Maybe Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Maybe a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Maybe a1)
type SequenceA (arg :: Maybe (f a)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: Maybe (f a))
type MapM (arg1 :: a ~> m b) (arg2 :: Maybe a) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: Maybe a)
type Sequence (arg :: Maybe (m a)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: Maybe (m a))
PTraversable [] Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: [a1]) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: [a1])
type SequenceA (arg :: [f a]) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (arg :: [f a])
type MapM (arg1 :: a ~> m b) (arg2 :: [a]) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (arg1 :: a ~> m b) (arg2 :: [a])
type Sequence (arg :: [m a]) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (arg :: [m a])
PTraversable (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PTraversable (Either a) Source # 
Instance details

Defined in Data.Traversable.Singletons

PTraversable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Associated Types

type Traverse (a2 :: a1 ~> f b) (a3 :: Proxy a1) 
Instance details

Defined in Data.Traversable.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Proxy a1)
type SequenceA (a2 :: Proxy (f a1)) 
Instance details

Defined in Data.Traversable.Singletons

type SequenceA (a2 :: Proxy (f a1))
type MapM (a2 :: a1 ~> m b) (a3 :: Proxy a1) 
Instance details

Defined in Data.Traversable.Singletons

type MapM (a2 :: a1 ~> m b) (a3 :: Proxy a1)
type Sequence (a2 :: Proxy (m a1)) 
Instance details

Defined in Data.Traversable.Singletons

type Sequence (a2 :: Proxy (m a1))
PTraversable ((,) a) Source # 
Instance details

Defined in Data.Traversable.Singletons

PTraversable (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

PTraversable (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

PTraversable (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

PTraversable (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

class (SFunctor t, SFoldable t) => STraversable (t :: Type -> Type) where Source #

Minimal complete definition

Nothing

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: t a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

default sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: t a). (Traverse t1 t2 ~ Traverse_6989586621680096875 t1 t2, SApplicative f) => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: t (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

default sSequenceA :: forall (f :: Type -> Type) a (t1 :: t (f a)). (SequenceA t1 ~ SequenceA_6989586621680096887 t1, SApplicative f) => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: t a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

default sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: t a). (MapM t1 t2 ~ MapM_6989586621680096897 t1 t2, SMonad m) => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: t (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

default sSequence :: forall (m :: Type -> Type) a (t1 :: t (m a)). (Sequence t1 ~ Sequence_6989586621680096911 t1, SMonad m) => Sing t1 -> Sing (Sequence t1) Source #

Instances

Instances details
STraversable First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: First a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: First (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: First a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: First (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Last a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Last (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Last a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Last (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Max a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Max (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Max a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Max (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Min a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Min (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Min a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Min (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable NonEmpty Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: NonEmpty a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: NonEmpty (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: NonEmpty a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: NonEmpty (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Identity Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Identity a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Identity (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Identity a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Identity (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable First Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: First a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: First (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: First a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: First (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Last Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Last a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Last (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Last a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Last (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Dual Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Dual a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Dual (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Dual a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Dual (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Product Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Product a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Product (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Product a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Product (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Sum Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Sum a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Sum (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Sum a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Sum (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable Maybe Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Maybe a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Maybe (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Maybe a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Maybe (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable [] Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: [a]). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: [f a]). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: [a]). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: [m a]). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sTraverse :: forall a0 (f :: Type -> Type) b (t1 :: a0 ~> f b) (t2 :: Arg a a0). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: Arg a (f a0)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: Arg a a0). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a0 (t1 :: Arg a (m a0)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable (Either a) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a0 (f :: Type -> Type) b (t1 :: a0 ~> f b) (t2 :: Either a a0). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: Either a (f a0)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: Either a a0). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a0 (t1 :: Either a (m a0)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Proxy a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Proxy (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Proxy a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Proxy (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable ((,) a) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a0 (f :: Type -> Type) b (t1 :: a0 ~> f b) (t2 :: (a, a0)). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: (a, f a0)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: (a, a0)). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a0 (t1 :: (a, m a0)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

STraversable (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Const m a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Const m (f a)). SApplicative f => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m0 :: Type -> Type) b (t1 :: a ~> m0 b) (t2 :: Const m a). SMonad m0 => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m0 :: Type -> Type) a (t1 :: Const m (m0 a)). SMonad m0 => Sing t1 -> Sing (Sequence t1) Source #

(STraversable f, STraversable g) => STraversable (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sTraverse :: forall a (f0 :: Type -> Type) b (t1 :: a ~> f0 b) (t2 :: Product f g a). SApplicative f0 => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Product f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Product f g a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Product f g (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

(STraversable f, STraversable g) => STraversable (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sTraverse :: forall a (f0 :: Type -> Type) b (t1 :: a ~> f0 b) (t2 :: Sum f g a). SApplicative f0 => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Sum f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Sum f g a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Sum f g (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

(STraversable f, STraversable g) => STraversable (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sTraverse :: forall a (f0 :: Type -> Type) b (t1 :: a ~> f0 b) (t2 :: Compose f g a). SApplicative f0 => Sing t1 -> Sing t2 -> Sing (Traverse t1 t2) Source #

sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Compose f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (SequenceA t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Compose f g a). SMonad m => Sing t1 -> Sing t2 -> Sing (MapM t1 t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Compose f g (m a)). SMonad m => Sing t1 -> Sing (Sequence t1) Source #

Miscellaneous functions

type family Id (a1 :: a) :: a where ... Source #

Equations

Id (x :: a) = x 

sId :: forall a (t :: a). Sing t -> Sing (Id t) Source #

type family Const (a1 :: a) (a2 :: b) :: a where ... Source #

Equations

Const (x :: a) (_1 :: b) = x 

sConst :: forall a b (t1 :: a) (t2 :: b). Sing t1 -> Sing t2 -> Sing (Const t1 t2) Source #

type family ((a1 :: b ~> c) . (a2 :: a ~> b)) (a3 :: a) :: c where ... infixr 9 Source #

Equations

((f :: b6989586621679154160 ~> k2) . (g :: k1 ~> b6989586621679154160)) (a_6989586621679154333 :: k1) = Apply (LamCases_6989586621679154345Sym0 f g a_6989586621679154333) a_6989586621679154333 

(%.) :: forall b c a (t1 :: b ~> c) (t2 :: a ~> b) (t3 :: a). Sing t1 -> Sing t2 -> Sing t3 -> Sing ((t1 . t2) t3) infixr 9 Source #

type family Flip (a1 :: a ~> (b ~> c)) (a2 :: b) (a3 :: a) :: c where ... Source #

Equations

Flip (f :: k2 ~> (k3 ~> k4)) (x :: k3) (y :: k2) = Apply (Apply f y) x 

sFlip :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: b) (t3 :: a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Flip t1 t2 t3) Source #

type family (a1 :: a ~> b) $ (a2 :: a) :: b where ... infixr 0 Source #

Equations

(f :: k1 ~> k2) $ (x :: k1) = Apply f x 

(%$) :: forall a b (t1 :: a ~> b) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 $ t2) infixr 0 Source #

type family Until (a1 :: a ~> Bool) (a2 :: a ~> a) (a3 :: a) :: a where ... Source #

Equations

Until (p :: k2 ~> Bool) (f :: k2 ~> k2) (a_6989586621679154275 :: k2) = Apply (Let6989586621679154287GoSym0 p f a_6989586621679154275) a_6989586621679154275 

sUntil :: forall a (t1 :: a ~> Bool) (t2 :: a ~> a) (t3 :: a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Until t1 t2 t3) Source #

type family AsTypeOf (a1 :: a) (a2 :: a) :: a where ... Source #

Equations

AsTypeOf (a_6989586621679154312 :: k1) (a_6989586621679154314 :: k1) = Apply (Apply (ConstSym0 :: TyFun k1 (k1 ~> k1) -> Type) a_6989586621679154312) a_6989586621679154314 

sAsTypeOf :: forall a (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (AsTypeOf t1 t2) Source #

type family Error (str :: Symbol) :: a where ... Source #

A promoted version of error. This implements Error as a stuck type family with a Symbol argument. Depending on your needs, you might also consider the following alternatives:

  • Data.Singletons.Base.PolyError provides PolyError, which generalizes the argument to be kind-polymorphic. This allows passing additional information to the error besides raw Symbols.
  • Data.Singletons.Base.TypeError provides TypeError, a slightly modified version of the custom type error machinery found in GHC.TypeLits. This allows emitting error messages as compiler errors rather than as stuck type families.

sError :: forall a (str :: Symbol). HasCallStack => Sing str -> Sing (Error str :: a) Source #

The singleton for error.

type family ErrorWithoutStackTrace (str :: Symbol) :: a where ... Source #

The promotion of errorWithoutStackTrace.

sErrorWithoutStackTrace :: forall a (str :: Symbol). Sing str -> Sing (ErrorWithoutStackTrace str :: a) Source #

The singleton for errorWithoutStackTrace.

type family Undefined :: forall a. a where ... Source #

The promotion of undefined.

type family Seq (a1 :: a) (a2 :: b) :: b where ... infixr 0 Source #

Equations

Seq (_1 :: a) (x :: b) = x 

sSeq :: forall a b (t1 :: a) (t2 :: b). Sing t1 -> Sing t2 -> Sing (Seq t1 t2) infixr 0 Source #

type family (a1 :: a ~> b) $! (a2 :: a) :: b where ... infixr 0 Source #

Equations

(f :: a6989586621679154152 ~> b6989586621679154153) $! (x :: a6989586621679154152) = Apply f (Let6989586621679154303VxSym0 f x) 

(%$!) :: forall a b (t1 :: a ~> b) (t2 :: a). Sing t1 -> Sing t2 -> Sing (t1 $! t2) infixr 0 Source #

List operations

type family Map (a1 :: a ~> b) (a2 :: [a]) :: [b] where ... Source #

Equations

Map (_1 :: a ~> b) ('[] :: [a]) = NilSym0 :: [b] 
Map (f :: a ~> b) (x ': xs :: [a]) = Apply (Apply ((:@#@$) :: TyFun b ([b] ~> [b]) -> Type) (Apply f x)) (Apply (Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) f) xs) 

sMap :: forall a b (t1 :: a ~> b) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Map t1 t2) Source #

type family (a1 :: [a]) ++ (a2 :: [a]) :: [a] where ... infixr 5 Source #

Equations

('[] :: [a]) ++ (ys :: [a]) = ys 
(x ': xs :: [a]) ++ (ys :: [a]) = Apply (Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) x) (Apply (Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) xs) ys) 

(%++) :: forall a (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (t1 ++ t2) infixr 5 Source #

type family Filter (a1 :: a ~> Bool) (a2 :: [a]) :: [a] where ... Source #

Equations

Filter (_p :: a ~> Bool) ('[] :: [a]) = NilSym0 :: [a] 
Filter (p :: k1 ~> Bool) (x ': xs :: [k1]) = Apply (LamCases_6989586621679544680Sym0 p x xs) (Apply p x) 

sFilter :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Filter t1 t2) Source #

type family Head (a1 :: [a]) :: a where ... Source #

Equations

Head (a2 ': _1 :: [a1]) = a2 
Head ('[] :: [a]) = Apply (ErrorSym0 :: TyFun Symbol a -> Type) "Data.Singletons.List.head: empty list" 

sHead :: forall a (t :: [a]). Sing t -> Sing (Head t) Source #

type family Last (a1 :: [a]) :: a where ... Source #

Equations

Last ('[] :: [a]) = Apply (ErrorSym0 :: TyFun Symbol a -> Type) "Data.Singletons.List.last: empty list" 
Last ('[x] :: [a]) = x 
Last (_1 ': (x ': xs) :: [k2]) = Apply (LastSym0 :: TyFun [k2] k2 -> Type) (Apply (Apply ((:@#@$) :: TyFun k2 ([k2] ~> [k2]) -> Type) x) xs) 

sLast :: forall a (t :: [a]). Sing t -> Sing (Last t) Source #

type family Tail (a1 :: [a]) :: [a] where ... Source #

Equations

Tail (_1 ': t :: [a]) = t 
Tail ('[] :: [a]) = Apply (ErrorSym0 :: TyFun Symbol [a] -> Type) "Data.Singletons.List.tail: empty list" 

sTail :: forall a (t :: [a]). Sing t -> Sing (Tail t) Source #

type family Init (a1 :: [a]) :: [a] where ... Source #

Equations

Init ('[] :: [a]) = Apply (ErrorSym0 :: TyFun Symbol [a] -> Type) "Data.Singletons.List.init: empty list" 
Init (x ': xs :: [k1]) = Apply (Apply (Let6989586621679545447Init'Sym0 x xs :: TyFun k1 ([k1] ~> [k1]) -> Type) x) xs 

sInit :: forall a (t :: [a]). Sing t -> Sing (Init t) Source #

type family (a1 :: [a]) !! (a2 :: Natural) :: a where ... infixl 9 Source #

Equations

('[] :: [a]) !! _1 = Apply (ErrorSym0 :: TyFun Symbol a -> Type) "Data.Singletons.List.!!: index too large" 
(x ': xs :: [k2]) !! n = Apply (LamCases_6989586621679544271Sym0 x xs n) (Apply (Apply ((==@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) n) (FromInteger 0 :: Natural)) 

(%!!) :: forall a (t1 :: [a]) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (t1 !! t2) infixl 9 Source #

type family Null (arg :: t a) :: Bool Source #

Instances

Instances details
type Null (arg :: First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: First a)
type Null (arg :: Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Last a)
type Null (arg :: Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Max a)
type Null (arg :: Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Min a)
type Null (arg :: NonEmpty a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: NonEmpty a)
type Null (a2 :: Identity a1) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

type Null (a2 :: Identity a1)
type Null (arg :: First a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: First a)
type Null (arg :: Last a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: Last a)
type Null (a2 :: Dual a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Dual a1)
type Null (a2 :: Product a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Product a1)
type Null (a2 :: Sum a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Sum a1)
type Null (arg :: Maybe a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: Maybe a)
type Null (a2 :: [a1]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: [a1])
type Null (arg :: Arg a1 a2) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Arg a1 a2)
type Null (a3 :: Either a1 a2) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (a3 :: Either a1 a2)
type Null (a2 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (a2 :: Proxy a1)
type Null (arg :: (a1, a2)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: (a1, a2))
type Null (arg :: Const m a) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Null (arg :: Const m a)
type Null (arg :: Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Null (arg :: Product f g a)
type Null (arg :: Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

type Null (arg :: Sum f g a)
type Null (arg :: Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

type Null (arg :: Compose f g a)

sNull :: forall a (t1 :: t a). SFoldable t => Sing t1 -> Sing (Null t1) Source #

type family Length (arg :: t a) :: Natural Source #

Instances

Instances details
type Length (arg :: First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: First a)
type Length (arg :: Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Last a)
type Length (arg :: Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Max a)
type Length (arg :: Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Min a)
type Length (arg :: NonEmpty a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: NonEmpty a)
type Length (a2 :: Identity a1) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

type Length (a2 :: Identity a1)
type Length (arg :: First a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: First a)
type Length (arg :: Last a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: Last a)
type Length (a2 :: Dual a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Dual a1)
type Length (a2 :: Product a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Product a1)
type Length (a2 :: Sum a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Sum a1)
type Length (arg :: Maybe a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: Maybe a)
type Length (a2 :: [a1]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: [a1])
type Length (arg :: Arg a1 a2) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Arg a1 a2)
type Length (a3 :: Either a1 a2) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (a3 :: Either a1 a2)
type Length (a2 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (a2 :: Proxy a1)
type Length (arg :: (a1, a2)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: (a1, a2))
type Length (arg :: Const m a) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Length (arg :: Const m a)
type Length (arg :: Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Length (arg :: Product f g a)
type Length (arg :: Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

type Length (arg :: Sum f g a)
type Length (arg :: Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

type Length (arg :: Compose f g a)

sLength :: forall a (t1 :: t a). SFoldable t => Sing t1 -> Sing (Length t1) Source #

type family Reverse (a1 :: [a]) :: [a] where ... Source #

Equations

Reverse (l :: [a6989586621679540816]) = Apply (Apply (Let6989586621679545431RevSym0 l :: TyFun [a6989586621679540816] ([a6989586621679540816] ~> [a6989586621679540816]) -> Type) l) (NilSym0 :: [a6989586621679540816]) 

sReverse :: forall a (t :: [a]). Sing t -> Sing (Reverse t) Source #

Special folds

type family And (a :: t Bool) :: Bool where ... Source #

Equations

And (a_6989586621679922374 :: t Bool) = Apply (Apply (Apply ((.@#@$) :: TyFun (All ~> Bool) ((t Bool ~> All) ~> (t Bool ~> Bool)) -> Type) GetAllSym0) (Apply (FoldMapSym0 :: TyFun (Bool ~> All) (t Bool ~> All) -> Type) All_Sym0)) a_6989586621679922374 

sAnd :: forall (t1 :: Type -> Type) (t2 :: t1 Bool). SFoldable t1 => Sing t2 -> Sing (And t2) Source #

type family Or (a :: t Bool) :: Bool where ... Source #

Equations

Or (a_6989586621679922368 :: t Bool) = Apply (Apply (Apply ((.@#@$) :: TyFun (Any ~> Bool) ((t Bool ~> Any) ~> (t Bool ~> Bool)) -> Type) GetAnySym0) (Apply (FoldMapSym0 :: TyFun (Bool ~> Any) (t Bool ~> Any) -> Type) Any_Sym0)) a_6989586621679922368 

sOr :: forall (t1 :: Type -> Type) (t2 :: t1 Bool). SFoldable t1 => Sing t2 -> Sing (Or t2) Source #

type family Any (a1 :: a ~> Bool) (a2 :: t a) :: Bool where ... Source #

Equations

Any (p :: a ~> Bool) (a_6989586621679922359 :: t a) = Apply (Apply (Apply ((.@#@$) :: TyFun (Any ~> Bool) ((t a ~> Any) ~> (t a ~> Bool)) -> Type) GetAnySym0) (Apply (FoldMapSym0 :: TyFun (a ~> Any) (t a ~> Any) -> Type) (Apply (Apply ((.@#@$) :: TyFun (Bool ~> Any) ((a ~> Bool) ~> (a ~> Any)) -> Type) Any_Sym0) p))) a_6989586621679922359 

sAny :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Any t2 t3) Source #

type family All (a1 :: a ~> Bool) (a2 :: t a) :: Bool where ... Source #

Equations

All (p :: a ~> Bool) (a_6989586621679922350 :: t a) = Apply (Apply (Apply ((.@#@$) :: TyFun (All ~> Bool) ((t a ~> All) ~> (t a ~> Bool)) -> Type) GetAllSym0) (Apply (FoldMapSym0 :: TyFun (a ~> All) (t a ~> All) -> Type) (Apply (Apply ((.@#@$) :: TyFun (Bool ~> All) ((a ~> Bool) ~> (a ~> All)) -> Type) All_Sym0) p))) a_6989586621679922350 

sAll :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (All t2 t3) Source #

type family Concat (a1 :: t [a]) :: [a] where ... Source #

Equations

Concat (xs :: t [a]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ([a] ~> ([a] ~> [a])) ([a] ~> (t [a] ~> [a])) -> Type) (LamCases_6989586621679922400Sym0 xs :: TyFun [a] (TyFun [a] [a] -> Type) -> Type)) (NilSym0 :: [a])) xs 

sConcat :: forall (t1 :: Type -> Type) a (t2 :: t1 [a]). SFoldable t1 => Sing t2 -> Sing (Concat t2) Source #

type family ConcatMap (a1 :: a ~> [b]) (a2 :: t a) :: [b] where ... Source #

Equations

ConcatMap (f :: a ~> [b6989586621679921893]) (xs :: t a) = Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> ([b6989586621679921893] ~> [b6989586621679921893])) ([b6989586621679921893] ~> (t a ~> [b6989586621679921893])) -> Type) (LamCases_6989586621679922387Sym0 f xs)) (NilSym0 :: [b6989586621679921893])) xs 

sConcatMap :: forall a b (t1 :: Type -> Type) (t2 :: a ~> [b]) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (ConcatMap t2 t3) Source #

Building lists

Scans

type family Scanl (a1 :: b ~> (a ~> b)) (a2 :: b) (a3 :: [a]) :: [b] where ... Source #

Equations

Scanl (f :: b6989586621679540686 ~> (a6989586621679540687 ~> b6989586621679540686)) (q :: b6989586621679540686) (ls :: [a6989586621679540687]) = Apply (Apply ((:@#@$) :: TyFun b6989586621679540686 ([b6989586621679540686] ~> [b6989586621679540686]) -> Type) q) (Apply (LamCases_6989586621679545232Sym0 f q ls) ls) 

sScanl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Scanl t1 t2 t3) Source #

type family Scanl1 (a1 :: a ~> (a ~> a)) (a2 :: [a]) :: [a] where ... Source #

Equations

Scanl1 (f :: k1 ~> (k1 ~> k1)) (x ': xs :: [k1]) = Apply (Apply (Apply (ScanlSym0 :: TyFun (k1 ~> (k1 ~> k1)) (k1 ~> ([k1] ~> [k1])) -> Type) f) x) xs 
Scanl1 (_1 :: a ~> (a ~> a)) ('[] :: [a]) = NilSym0 :: [a] 

sScanl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Scanl1 t1 t2) Source #

type family Scanr (a1 :: a ~> (b ~> b)) (a2 :: b) (a3 :: [a]) :: [b] where ... Source #

Equations

Scanr (_1 :: a ~> (k1 ~> k1)) (q0 :: k1) ('[] :: [a]) = Apply (Apply ((:@#@$) :: TyFun k1 ([k1] ~> [k1]) -> Type) q0) (NilSym0 :: [k1]) 
Scanr (f :: a ~> (k1 ~> k1)) (q0 :: k1) (x ': xs :: [a]) = Apply (LamCases_6989586621679545207Sym0 f q0 x xs) (Apply (Apply (Apply (ScanrSym0 :: TyFun (a ~> (k1 ~> k1)) (k1 ~> ([a] ~> [k1])) -> Type) f) q0) xs) 

sScanr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Scanr t1 t2 t3) Source #

type family Scanr1 (a1 :: a ~> (a ~> a)) (a2 :: [a]) :: [a] where ... Source #

Equations

Scanr1 (_1 :: a ~> (a ~> a)) ('[] :: [a]) = NilSym0 :: [a] 
Scanr1 (_1 :: k1 ~> (k1 ~> k1)) ('[x] :: [k1]) = Apply (Apply ((:@#@$) :: TyFun k1 ([k1] ~> [k1]) -> Type) x) (NilSym0 :: [k1]) 
Scanr1 (f :: k1 ~> (k1 ~> k1)) (x ': (wild_6989586621679541173 ': wild_6989586621679541175) :: [k1]) = Apply (LamCases_6989586621679545188Sym0 f x wild_6989586621679541173 wild_6989586621679541175) (Apply (Apply (Scanr1Sym0 :: TyFun (k1 ~> (k1 ~> k1)) ([k1] ~> [k1]) -> Type) f) (Let6989586621679545186XsSym0 f x wild_6989586621679541173 wild_6989586621679541175)) 

sScanr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Scanr1 t1 t2) Source #

Infinite lists

type family Replicate (a1 :: Natural) (a2 :: a) :: [a] where ... Source #

Equations

Replicate n (x :: a6989586621679540590) = Apply (LamCases_6989586621679544290Sym0 n x) (Apply (Apply ((==@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) n) (FromInteger 0 :: Natural)) 

sReplicate :: forall a (t1 :: Natural) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Replicate t1 t2) Source #

Sublists

type family Take (a1 :: Natural) (a2 :: [a]) :: [a] where ... Source #

Equations

Take _1 ('[] :: [a]) = NilSym0 :: [a] 
Take n (x ': xs :: [a]) = Apply (LamCases_6989586621679544450Sym0 n x xs) (Apply (Apply ((==@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) n) (FromInteger 0 :: Natural)) 

sTake :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Take t1 t2) Source #

type family Drop (a1 :: Natural) (a2 :: [a]) :: [a] where ... Source #

Equations

Drop _1 ('[] :: [a]) = NilSym0 :: [a] 
Drop n (x ': xs :: [a]) = Apply (LamCases_6989586621679544437Sym0 n x xs) (Apply (Apply ((==@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) n) (FromInteger 0 :: Natural)) 

sDrop :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Drop t1 t2) Source #

type family TakeWhile (a1 :: a ~> Bool) (a2 :: [a]) :: [a] where ... Source #

Equations

TakeWhile (_1 :: a ~> Bool) ('[] :: [a]) = NilSym0 :: [a] 
TakeWhile (p :: k1 ~> Bool) (x ': xs :: [k1]) = Apply (LamCases_6989586621679544579Sym0 p x xs) (Apply p x) 

sTakeWhile :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (TakeWhile t1 t2) Source #

type family DropWhile (a1 :: a ~> Bool) (a2 :: [a]) :: [a] where ... Source #

Equations

DropWhile (_1 :: a ~> Bool) ('[] :: [a]) = NilSym0 :: [a] 
DropWhile (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Apply (LamCases_6989586621679544566Sym0 p x xs') (Apply p x) 

sDropWhile :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (DropWhile t1 t2) Source #

type family Span (a1 :: a ~> Bool) (a2 :: [a]) :: ([a], [a]) where ... Source #

Equations

Span (_1 :: a ~> Bool) ('[] :: [a]) = Apply (Apply (Tuple2Sym0 :: TyFun [a] ([a] ~> ([a], [a])) -> Type) (Let6989586621679544499XsSym0 :: [a])) (Let6989586621679544499XsSym0 :: [a]) 
Span (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Apply (LamCases_6989586621679544506Sym0 p x xs') (Apply p x) 

sSpan :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Span t1 t2) Source #

type family Break (a1 :: a ~> Bool) (a2 :: [a]) :: ([a], [a]) where ... Source #

Equations

Break (_1 :: a ~> Bool) ('[] :: [a]) = Apply (Apply (Tuple2Sym0 :: TyFun [a] ([a] ~> ([a], [a])) -> Type) (Let6989586621679544460XsSym0 :: [a])) (Let6989586621679544460XsSym0 :: [a]) 
Break (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Apply (LamCases_6989586621679544467Sym0 p x xs') (Apply p x) 

sBreak :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Break t1 t2) Source #

type family SplitAt (a1 :: Natural) (a2 :: [a]) :: ([a], [a]) where ... Source #

Equations

SplitAt n (xs :: [a]) = Apply (Apply (Tuple2Sym0 :: TyFun [a] ([a] ~> ([a], [a])) -> Type) (Apply (Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) n) xs)) (Apply (Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) n) xs) 

sSplitAt :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (SplitAt t1 t2) Source #

Searching lists

type family NotElem (a1 :: a) (a2 :: t a) :: Bool where ... Source #

Equations

NotElem (x :: k1) (a_6989586621679922301 :: t k1) = Apply (Apply (Apply ((.@#@$) :: TyFun (Bool ~> Bool) ((t k1 ~> Bool) ~> (t k1 ~> Bool)) -> Type) NotSym0) (Apply (ElemSym0 :: TyFun k1 (t k1 ~> Bool) -> Type) x)) a_6989586621679922301 

sNotElem :: forall a (t1 :: Type -> Type) (t2 :: a) (t3 :: t1 a). (SFoldable t1, SEq a) => Sing t2 -> Sing t3 -> Sing (NotElem t2 t3) Source #

type family Lookup (a1 :: a) (a2 :: [(a, b)]) :: Maybe b where ... Source #

Equations

Lookup (_key :: a) ('[] :: [(a, b)]) = NothingSym0 :: Maybe b 
Lookup (key :: k2) ('(x, y) ': xys :: [(k2, k3)]) = Apply (LamCases_6989586621679544356Sym0 key x y xys) (Apply (Apply ((==@#@$) :: TyFun k2 (k2 ~> Bool) -> Type) key) x) 

sLookup :: forall a b (t1 :: a) (t2 :: [(a, b)]). SEq a => Sing t1 -> Sing t2 -> Sing (Lookup t1 t2) Source #

Zipping and unzipping lists

type family Zip (a1 :: [a]) (a2 :: [b]) :: [(a, b)] where ... Source #

Equations

Zip (x ': xs :: [a]) (y ': ys :: [b]) = Apply (Apply ((:@#@$) :: TyFun (a, b) ([(a, b)] ~> [(a, b)]) -> Type) (Apply (Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) x) y)) (Apply (Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) xs) ys) 
Zip ('[] :: [a]) ('[] :: [b]) = NilSym0 :: [(a, b)] 
Zip (_1 ': _2 :: [a]) ('[] :: [b]) = NilSym0 :: [(a, b)] 
Zip ('[] :: [a]) (_1 ': _2 :: [b]) = NilSym0 :: [(a, b)] 

sZip :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (Zip t1 t2) Source #

type family Zip3 (a1 :: [a]) (a2 :: [b]) (a3 :: [c]) :: [(a, b, c)] where ... Source #

Equations

Zip3 (a2 ': as :: [a1]) (b2 ': bs :: [b1]) (c2 ': cs :: [c1]) = Apply (Apply ((:@#@$) :: TyFun (a1, b1, c1) ([(a1, b1, c1)] ~> [(a1, b1, c1)]) -> Type) (Apply (Apply (Apply (Tuple3Sym0 :: TyFun a1 (b1 ~> (c1 ~> (a1, b1, c1))) -> Type) a2) b2) c2)) (Apply (Apply (Apply (Zip3Sym0 :: TyFun [a1] ([b1] ~> ([c1] ~> [(a1, b1, c1)])) -> Type) as) bs) cs) 
Zip3 ('[] :: [a]) ('[] :: [b]) ('[] :: [c]) = NilSym0 :: [(a, b, c)] 
Zip3 ('[] :: [a]) ('[] :: [b]) (_1 ': _2 :: [c]) = NilSym0 :: [(a, b, c)] 
Zip3 ('[] :: [a]) (_1 ': _2 :: [b]) ('[] :: [c]) = NilSym0 :: [(a, b, c)] 
Zip3 ('[] :: [a]) (_1 ': _2 :: [b]) (_3 ': _4 :: [c]) = NilSym0 :: [(a, b, c)] 
Zip3 (_1 ': _2 :: [a]) ('[] :: [b]) ('[] :: [c]) = NilSym0 :: [(a, b, c)] 
Zip3 (_1 ': _2 :: [a]) ('[] :: [b]) (_3 ': _4 :: [c]) = NilSym0 :: [(a, b, c)] 
Zip3 (_1 ': _2 :: [a]) (_3 ': _4 :: [b]) ('[] :: [c]) = NilSym0 :: [(a, b, c)] 

sZip3 :: forall a b c (t1 :: [a]) (t2 :: [b]) (t3 :: [c]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Zip3 t1 t2 t3) Source #

type family ZipWith (a1 :: a ~> (b ~> c)) (a2 :: [a]) (a3 :: [b]) :: [c] where ... Source #

Equations

ZipWith (f :: a ~> (b ~> c)) (x ': xs :: [a]) (y ': ys :: [b]) = Apply (Apply ((:@#@$) :: TyFun c ([c] ~> [c]) -> Type) (Apply (Apply f x) y)) (Apply (Apply (Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) f) xs) ys) 
ZipWith (_1 :: a ~> (b ~> c)) ('[] :: [a]) ('[] :: [b]) = NilSym0 :: [c] 
ZipWith (_1 :: a ~> (b ~> c)) (_2 ': _3 :: [a]) ('[] :: [b]) = NilSym0 :: [c] 
ZipWith (_1 :: a ~> (b ~> c)) ('[] :: [a]) (_2 ': _3 :: [b]) = NilSym0 :: [c] 

sZipWith :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: [a]) (t3 :: [b]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ZipWith t1 t2 t3) Source #

type family ZipWith3 (a1 :: a ~> (b ~> (c ~> d))) (a2 :: [a]) (a3 :: [b]) (a4 :: [c]) :: [d] where ... Source #

Equations

ZipWith3 (z :: a1 ~> (b1 ~> (c1 ~> d))) (a2 ': as :: [a1]) (b2 ': bs :: [b1]) (c2 ': cs :: [c1]) = Apply (Apply ((:@#@$) :: TyFun d ([d] ~> [d]) -> Type) (Apply (Apply (Apply z a2) b2) c2)) (Apply (Apply (Apply (Apply (ZipWith3Sym0 :: TyFun (a1 ~> (b1 ~> (c1 ~> d))) ([a1] ~> ([b1] ~> ([c1] ~> [d]))) -> Type) z) as) bs) cs) 
ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) ('[] :: [a]) ('[] :: [b]) ('[] :: [c]) = NilSym0 :: [d] 
ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) ('[] :: [a]) ('[] :: [b]) (_2 ': _3 :: [c]) = NilSym0 :: [d] 
ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) ('[] :: [a]) (_2 ': _3 :: [b]) ('[] :: [c]) = NilSym0 :: [d] 
ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) ('[] :: [a]) (_2 ': _3 :: [b]) (_4 ': _5 :: [c]) = NilSym0 :: [d] 
ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) (_2 ': _3 :: [a]) ('[] :: [b]) ('[] :: [c]) = NilSym0 :: [d] 
ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) (_2 ': _3 :: [a]) ('[] :: [b]) (_4 ': _5 :: [c]) = NilSym0 :: [d] 
ZipWith3 (_1 :: a ~> (b ~> (c ~> d))) (_2 ': _3 :: [a]) (_4 ': _5 :: [b]) ('[] :: [c]) = NilSym0 :: [d] 

sZipWith3 :: forall a b c d (t1 :: a ~> (b ~> (c ~> d))) (t2 :: [a]) (t3 :: [b]) (t4 :: [c]). Sing t1 -> Sing t2 -> Sing t3 -> Sing t4 -> Sing (ZipWith3 t1 t2 t3 t4) Source #

type family Unzip (a1 :: [(a, b)]) :: ([a], [b]) where ... Source #

Equations

Unzip (xs :: [(k2, k3)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3) ~> (([k2], [k3]) ~> ([k2], [k3]))) (([k2], [k3]) ~> ([(k2, k3)] ~> ([k2], [k3]))) -> Type) (LamCases_6989586621679544931Sym0 xs :: TyFun (k2, k3) (TyFun ([k2], [k3]) ([k2], [k3]) -> Type) -> Type)) (Apply (Apply (Tuple2Sym0 :: TyFun [k2] ([k3] ~> ([k2], [k3])) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3]))) xs 

sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Unzip t) Source #

type family Unzip3 (a1 :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #

Equations

Unzip3 (xs :: [(k2, k3, k4)]) = Apply (Apply (Apply (FoldrSym0 :: TyFun ((k2, k3, k4) ~> (([k2], [k3], [k4]) ~> ([k2], [k3], [k4]))) (([k2], [k3], [k4]) ~> ([(k2, k3, k4)] ~> ([k2], [k3], [k4]))) -> Type) (LamCases_6989586621679544914Sym0 xs :: TyFun (k2, k3, k4) (TyFun ([k2], [k3], [k4]) ([k2], [k3], [k4]) -> Type) -> Type)) (Apply (Apply (Apply (Tuple3Sym0 :: TyFun [k2] ([k3] ~> ([k4] ~> ([k2], [k3], [k4]))) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3])) (NilSym0 :: [k4]))) xs 

sUnzip3 :: forall a b c (t :: [(a, b, c)]). Sing t -> Sing (Unzip3 t) Source #

Functions on Symbols

type family Unlines (a :: [Symbol]) :: Symbol where ... Source #

Equations

Unlines ('[] :: [Symbol]) = "" 
Unlines (l ': ls) = Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) l) (Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) "\n") (Apply UnlinesSym0 ls)) 

sUnlines :: forall (t :: [Symbol]). Sing t -> Sing (Unlines t) Source #

type family Unwords (a :: [Symbol]) :: Symbol where ... Source #

Equations

Unwords ('[] :: [Symbol]) = "" 
Unwords (w ': ws) = Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) w) (Apply (Let6989586621679544812GoSym0 w ws) ws) 

sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Unwords t) Source #

Converting to and from Symbol

Converting to Symbol

type SymbolS = Symbol -> Symbol Source #

The shows functions return a function that prepends the output Symbol to an existing Symbol. This allows constant-time concatenation of results using function composition.

show_ :: Show a => a -> String Source #

show, but with an extra underscore so that its promoted counterpart (Show_) will not clash with the Show class.

class PShow a Source #

Associated Types

type ShowsPrec (arg :: Natural) (arg1 :: a) (arg2 :: Symbol) :: Symbol Source #

type ShowsPrec (arg :: Natural) (arg1 :: a) (arg2 :: Symbol) = ShowsPrec_6989586621679807423 arg arg1 arg2

type Show_ (arg :: a) :: Symbol Source #

type Show_ (arg :: a) = Show__6989586621679807435 arg

type ShowList (arg :: [a]) (arg1 :: Symbol) :: Symbol Source #

type ShowList (arg :: [a]) (arg1 :: Symbol) = ShowList_6989586621679807443 arg arg1

Instances

Instances details
PShow Void Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec a1 (a2 :: Void) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: Void) a3
type Show_ (arg :: Void) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Void)
type ShowList (arg1 :: [Void]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Void]) arg2
PShow All Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type ShowsPrec a1 (a2 :: All) a3 
Instance details

Defined in Data.Semigroup.Singletons

type ShowsPrec a1 (a2 :: All) a3
type Show_ (arg :: All) 
Instance details

Defined in Data.Semigroup.Singletons

type Show_ (arg :: All)
type ShowList (arg :: [All]) arg1 
Instance details

Defined in Data.Semigroup.Singletons

type ShowList (arg :: [All]) arg1
PShow Any Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type ShowsPrec a1 (a2 :: Any) a3 
Instance details

Defined in Data.Semigroup.Singletons

type ShowsPrec a1 (a2 :: Any) a3
type Show_ (arg :: Any) 
Instance details

Defined in Data.Semigroup.Singletons

type Show_ (arg :: Any)
type ShowList (arg :: [Any]) arg1 
Instance details

Defined in Data.Semigroup.Singletons

type ShowList (arg :: [Any]) arg1
PShow Ordering Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec a1 (a2 :: Ordering) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: Ordering) a3
type Show_ (arg :: Ordering) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Ordering)
type ShowList (arg1 :: [Ordering]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Ordering]) arg2
PShow Natural Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec _1 (n :: Natural) x 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec _1 (n :: Natural) x
type Show_ (arg :: Natural) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Natural)
type ShowList (arg1 :: [Natural]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Natural]) arg2
PShow () Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec a1 (a2 :: ()) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: ()) a3
type Show_ (arg :: ()) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: ())
type ShowList (arg1 :: [()]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [()]) arg2
PShow Bool Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec a1 (a2 :: Bool) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: Bool) a3
type Show_ (arg :: Bool) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Bool)
type ShowList (arg1 :: [Bool]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Bool]) arg2
PShow Char Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec p (c :: Char) x 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec p (c :: Char) x
type Show_ (arg :: Char) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Char)
type ShowList (cs :: [Char]) x 
Instance details

Defined in Text.Show.Singletons

type ShowList (cs :: [Char]) x
PShow Symbol Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec _1 (s :: Symbol) x 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec _1 (s :: Symbol) x
type Show_ (arg :: Symbol) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Symbol)
type ShowList (arg1 :: [Symbol]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Symbol]) arg2
PShow (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (NonEmpty a) Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

PShow (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PShow (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PShow (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Maybe a) Source # 
Instance details

Defined in Text.Show.Singletons

PShow [a] Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Either a b) Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

PShow (a, b) Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

class SShow a where Source #

Minimal complete definition

Nothing

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

default sShowsPrec :: forall (t1 :: Natural) (t2 :: a) (t3 :: Symbol). ShowsPrec t1 t2 t3 ~ ShowsPrec_6989586621679807423 t1 t2 t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: a). Sing t -> Sing (Show_ t) Source #

default sShow_ :: forall (t :: a). Show_ t ~ Show__6989586621679807435 t => Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

default sShowList :: forall (t1 :: [a]) (t2 :: Symbol). ShowList t1 t2 ~ ShowList_6989586621679807443 t1 t2 => Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

Instances

Instances details
SShow Void Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Void) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Void). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Void]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow Bool => SShow All Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: All) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: All). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [All]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow Bool => SShow Any Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Any) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Any). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Any]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow Ordering Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Ordering) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Ordering). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Ordering]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow Natural Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Natural) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Natural). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Natural]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow () Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: ()) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: ()). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [()]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow Bool Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Bool) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Bool). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Bool]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow Char Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Char) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Char). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Char]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow Symbol Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Symbol) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Symbol). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Symbol]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: First a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: First a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Last a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Last a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Max a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Max a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Max a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Min a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Min a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Min a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow m => SShow (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: WrappedMonoid m) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: WrappedMonoid m). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [WrappedMonoid m]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow [a]) => SShow (NonEmpty a) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: NonEmpty a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: NonEmpty a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [NonEmpty a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Identity a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Identity a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Identity a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow (Maybe a) => SShow (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: First a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: First a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow (Maybe a) => SShow (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Last a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Last a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Dual a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Dual a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Dual a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Product a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Product a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Product a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Sum a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Sum a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Sum a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Maybe a) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Maybe a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Maybe a). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Maybe a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow [a] Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: [a]) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: [a]). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [[a]]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow b) => SShow (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Arg a b) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Arg a b). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Arg a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow b) => SShow (Either a b) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Either a b) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Either a b). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Either a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Proxy s) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Proxy s). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Proxy s]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow b) => SShow (a, b) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: (a, b)). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [(a, b)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

SShow a => SShow (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Const a b) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: Const a b). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [Const a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow b, SShow c) => SShow (a, b, c) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: (a, b, c)). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [(a, b, c)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow b, SShow c, SShow d) => SShow (a, b, c, d) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c, d)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: (a, b, c, d)). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [(a, b, c, d)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow b, SShow c, SShow d, SShow e) => SShow (a, b, c, d, e) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c, d, e)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: (a, b, c, d, e)). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [(a, b, c, d, e)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow b, SShow c, SShow d, SShow e, SShow f) => SShow (a, b, c, d, e, f) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c, d, e, f)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: (a, b, c, d, e, f)). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [(a, b, c, d, e, f)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

(SShow a, SShow b, SShow c, SShow d, SShow e, SShow f, SShow g) => SShow (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c, d, e, f, g)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowsPrec t1 t2 t3) Source #

sShow_ :: forall (t :: (a, b, c, d, e, f, g)). Sing t -> Sing (Show_ t) Source #

sShowList :: forall (t1 :: [(a, b, c, d, e, f, g)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowList t1 t2) Source #

type family Shows (a1 :: a) (a2 :: Symbol) :: Symbol where ... Source #

Equations

Shows (s :: k1) a_6989586621679807396 = Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (k1 ~> (Symbol ~> Symbol)) -> Type) (FromInteger 0 :: Natural)) s) a_6989586621679807396 

sShows :: forall a (t1 :: a) (t2 :: Symbol). SShow a => Sing t1 -> Sing t2 -> Sing (Shows t1 t2) Source #

type family ShowChar (a :: Char) (a1 :: Symbol) :: Symbol where ... Source #

Equations

ShowChar a_6989586621679807368 a_6989586621679807370 = Apply (Apply ConsSymbolSym0 a_6989586621679807368) a_6989586621679807370 

sShowChar :: forall (t1 :: Char) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowChar t1 t2) Source #

type family ShowString (a :: Symbol) (a1 :: Symbol) :: Symbol where ... Source #

Equations

ShowString a_6989586621679807357 a_6989586621679807359 = Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) a_6989586621679807357) a_6989586621679807359 

sShowString :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (ShowString t1 t2) Source #

type family ShowParen (a :: Bool) (a1 :: Symbol ~> Symbol) (a2 :: Symbol) :: Symbol where ... Source #

Equations

ShowParen b p a_6989586621679807340 = Apply (Apply (LamCases_6989586621679807352Sym0 b p a_6989586621679807340) b) a_6989586621679807340 

sShowParen :: forall (t1 :: Bool) (t2 :: Symbol ~> Symbol) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (ShowParen t1 t2 t3) Source #

Defunctionalization symbols

Basic data types

type family FalseSym0 :: Bool where ... Source #

Equations

FalseSym0 = 'False 

type family TrueSym0 :: Bool where ... Source #

Equations

TrueSym0 = 'True 

data IfSym0 (a :: TyFun Bool (k ~> (k ~> k))) Source #

Instances

Instances details
SingI (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) #

SuppressUnusedWarnings (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679124436 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679124436 :: Bool) = IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type

data IfSym1 (a6989586621679124436 :: Bool) (b :: TyFun k (k ~> k)) Source #

Instances

Instances details
SingI1 (IfSym1 :: Bool -> TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (IfSym1 x :: TyFun k (k ~> k) -> Type) #

SingI c => SingI (IfSym1 c :: TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym1 c :: TyFun k (k ~> k) -> Type) #

SuppressUnusedWarnings (IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type) (a6989586621679124437 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym1 a6989586621679124436 :: TyFun k (k ~> k) -> Type) (a6989586621679124437 :: k) = IfSym2 a6989586621679124436 a6989586621679124437

data IfSym2 (a6989586621679124436 :: Bool) (a6989586621679124437 :: k) (c :: TyFun k k) Source #

Instances

Instances details
SingI2 (IfSym2 :: Bool -> k2 -> TyFun k2 k2 -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing2 :: forall (x :: Bool) (y :: k2). Sing x -> Sing y -> Sing (IfSym2 x y) #

SingI c => SingI1 (IfSym2 c :: k1 -> TyFun k1 k1 -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (IfSym2 c x) #

(SingI c, SingI t) => SingI (IfSym2 c t :: TyFun k k -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (IfSym2 c t) #

SuppressUnusedWarnings (IfSym2 a6989586621679124436 a6989586621679124437 :: TyFun k k -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym2 a6989586621679124436 a6989586621679124437 :: TyFun k k -> Type) (a6989586621679124438 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym2 a6989586621679124436 a6989586621679124437 :: TyFun k k -> Type) (a6989586621679124438 :: k) = If a6989586621679124436 a6989586621679124437 a6989586621679124438

type family IfSym3 (a6989586621679124436 :: Bool) (a6989586621679124437 :: k) (a6989586621679124438 :: k) :: k where ... Source #

Equations

IfSym3 a6989586621679124436 (a6989586621679124437 :: k) (a6989586621679124438 :: k) = If a6989586621679124436 a6989586621679124437 a6989586621679124438 

data (&&@#@$) (a :: TyFun Bool (Bool ~> Bool)) infixr 3 Source #

Instances

Instances details
SingI (&&@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (&&@#@$) #

SuppressUnusedWarnings (&&@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (&&@#@$) (a6989586621679123502 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (&&@#@$) (a6989586621679123502 :: Bool) = (&&@#@$$) a6989586621679123502

data (a6989586621679123502 :: Bool) &&@#@$$ (b :: TyFun Bool Bool) infixr 3 Source #

Instances

Instances details
SingI x => SingI ((&&@#@$$) x :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing ((&&@#@$$) x) #

SuppressUnusedWarnings ((&&@#@$$) a6989586621679123502 :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((&&@#@$$) a6989586621679123502 :: TyFun Bool Bool -> Type) (a6989586621679123503 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((&&@#@$$) a6989586621679123502 :: TyFun Bool Bool -> Type) (a6989586621679123503 :: Bool) = a6989586621679123502 && a6989586621679123503

type family (a6989586621679123502 :: Bool) &&@#@$$$ (a6989586621679123503 :: Bool) :: Bool where ... infixr 3 Source #

Equations

a6989586621679123502 &&@#@$$$ a6989586621679123503 = a6989586621679123502 && a6989586621679123503 

data (||@#@$) (a :: TyFun Bool (Bool ~> Bool)) infixr 2 Source #

Instances

Instances details
SingI (||@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing (||@#@$) #

SuppressUnusedWarnings (||@#@$) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (||@#@$) (a6989586621679123865 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (||@#@$) (a6989586621679123865 :: Bool) = (||@#@$$) a6989586621679123865

data (a6989586621679123865 :: Bool) ||@#@$$ (b :: TyFun Bool Bool) infixr 2 Source #

Instances

Instances details
SingI x => SingI ((||@#@$$) x :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing ((||@#@$$) x) #

SuppressUnusedWarnings ((||@#@$$) a6989586621679123865 :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((||@#@$$) a6989586621679123865 :: TyFun Bool Bool -> Type) (a6989586621679123866 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((||@#@$$) a6989586621679123865 :: TyFun Bool Bool -> Type) (a6989586621679123866 :: Bool) = a6989586621679123865 || a6989586621679123866

type family (a6989586621679123865 :: Bool) ||@#@$$$ (a6989586621679123866 :: Bool) :: Bool where ... infixr 2 Source #

Equations

a6989586621679123865 ||@#@$$$ a6989586621679123866 = a6989586621679123865 || a6989586621679123866 

data NotSym0 (a :: TyFun Bool Bool) Source #

Instances

Instances details
SingI NotSym0 Source # 
Instance details

Defined in Data.Bool.Singletons

Methods

sing :: Sing NotSym0 #

SuppressUnusedWarnings NotSym0 Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply NotSym0 (a6989586621679124212 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply NotSym0 (a6989586621679124212 :: Bool) = Not a6989586621679124212

type family NotSym1 (a6989586621679124212 :: Bool) :: Bool where ... Source #

Equations

NotSym1 a6989586621679124212 = Not a6989586621679124212 

type family OtherwiseSym0 :: Bool where ... Source #

type family NothingSym0 :: Maybe a where ... Source #

Equations

NothingSym0 = 'Nothing :: Maybe a 

data JustSym0 (a1 :: TyFun a (Maybe a)) Source #

Instances

Instances details
SingI (JustSym0 :: TyFun a (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (JustSym0 :: TyFun a (Maybe a) -> Type) #

SuppressUnusedWarnings (JustSym0 :: TyFun a (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679050265 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679050265 :: a) = 'Just a6989586621679050265

type family JustSym1 (a6989586621679050265 :: a) :: Maybe a where ... Source #

Equations

JustSym1 (a6989586621679050265 :: a) = 'Just a6989586621679050265 

data Maybe_Sym0 (a1 :: TyFun b ((a ~> b) ~> (Maybe a ~> b))) Source #

Instances

Instances details
SingI (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) #

SuppressUnusedWarnings (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679387993 :: b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679387993 :: b) = Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type

data Maybe_Sym1 (a6989586621679387993 :: b) (b1 :: TyFun (a ~> b) (Maybe a ~> b)) Source #

Instances

Instances details
SingI1 (Maybe_Sym1 :: b -> TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Maybe_Sym1 x :: TyFun (a ~> b) (Maybe a ~> b) -> Type) #

SingI d => SingI (Maybe_Sym1 d :: TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym1 d :: TyFun (a ~> b) (Maybe a ~> b) -> Type) #

SuppressUnusedWarnings (Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679387994 :: a ~> b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679387993 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679387994 :: a ~> b) = Maybe_Sym2 a6989586621679387993 a6989586621679387994

data Maybe_Sym2 (a6989586621679387993 :: b) (a6989586621679387994 :: a ~> b) (c :: TyFun (Maybe a) b) Source #

Instances

Instances details
SingI2 (Maybe_Sym2 :: b -> (a ~> b) -> TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing2 :: forall (x :: b) (y :: a ~> b). Sing x -> Sing y -> Sing (Maybe_Sym2 x y) #

SingI d => SingI1 (Maybe_Sym2 d :: (a ~> b) -> TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (Maybe_Sym2 d x) #

(SingI d1, SingI d2) => SingI (Maybe_Sym2 d1 d2 :: TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (Maybe_Sym2 d1 d2) #

SuppressUnusedWarnings (Maybe_Sym2 a6989586621679387993 a6989586621679387994 :: TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym2 a6989586621679387993 a6989586621679387994 :: TyFun (Maybe a) b -> Type) (a6989586621679387995 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym2 a6989586621679387993 a6989586621679387994 :: TyFun (Maybe a) b -> Type) (a6989586621679387995 :: Maybe a) = Maybe_ a6989586621679387993 a6989586621679387994 a6989586621679387995

type family Maybe_Sym3 (a6989586621679387993 :: b) (a6989586621679387994 :: a ~> b) (a6989586621679387995 :: Maybe a) :: b where ... Source #

Equations

Maybe_Sym3 (a6989586621679387993 :: b) (a6989586621679387994 :: a ~> b) (a6989586621679387995 :: Maybe a) = Maybe_ a6989586621679387993 a6989586621679387994 a6989586621679387995 

data LeftSym0 (a1 :: TyFun a (Either a b)) Source #

Instances

Instances details
SingI (LeftSym0 :: TyFun a (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (LeftSym0 :: TyFun a (Either a b) -> Type) #

SuppressUnusedWarnings (LeftSym0 :: TyFun a (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (LeftSym0 :: TyFun a (Either a b) -> Type) (a6989586621679050337 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (LeftSym0 :: TyFun a (Either a b) -> Type) (a6989586621679050337 :: a) = 'Left a6989586621679050337 :: Either a b

type family LeftSym1 (a6989586621679050337 :: a) :: Either a b where ... Source #

Equations

LeftSym1 (a6989586621679050337 :: a) = 'Left a6989586621679050337 :: Either a b 

data RightSym0 (a1 :: TyFun b (Either a b)) Source #

Instances

Instances details
SingI (RightSym0 :: TyFun b (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (RightSym0 :: TyFun b (Either a b) -> Type) #

SuppressUnusedWarnings (RightSym0 :: TyFun b (Either a b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (RightSym0 :: TyFun b (Either a b) -> Type) (a6989586621679050339 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (RightSym0 :: TyFun b (Either a b) -> Type) (a6989586621679050339 :: b) = 'Right a6989586621679050339 :: Either a b

type family RightSym1 (a6989586621679050339 :: b) :: Either a b where ... Source #

Equations

RightSym1 (a6989586621679050339 :: b) = 'Right a6989586621679050339 :: Either a b 

data Either_Sym0 (a1 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c))) Source #

Instances

Instances details
SingI (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) #

SuppressUnusedWarnings (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679259290 :: a ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679259290 :: a ~> c) = Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type

data Either_Sym1 (a6989586621679259290 :: a ~> c) (b1 :: TyFun (b ~> c) (Either a b ~> c)) Source #

Instances

Instances details
SingI1 (Either_Sym1 :: (a ~> c) -> TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing :: forall (x :: a ~> c). Sing x -> Sing (Either_Sym1 x :: TyFun (b ~> c) (Either a b ~> c) -> Type) #

SingI d => SingI (Either_Sym1 d :: TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym1 d :: TyFun (b ~> c) (Either a b ~> c) -> Type) #

SuppressUnusedWarnings (Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679259291 :: b ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym1 a6989586621679259290 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679259291 :: b ~> c) = Either_Sym2 a6989586621679259290 a6989586621679259291

data Either_Sym2 (a6989586621679259290 :: a ~> c) (a6989586621679259291 :: b ~> c) (c1 :: TyFun (Either a b) c) Source #

Instances

Instances details
SingI2 (Either_Sym2 :: (a ~> c) -> (b ~> c) -> TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing2 :: forall (x :: a ~> c) (y :: b ~> c). Sing x -> Sing y -> Sing (Either_Sym2 x y) #

SingI d => SingI1 (Either_Sym2 d :: (b ~> c) -> TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

liftSing :: forall (x :: b ~> c). Sing x -> Sing (Either_Sym2 d x) #

(SingI d1, SingI d2) => SingI (Either_Sym2 d1 d2 :: TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

Methods

sing :: Sing (Either_Sym2 d1 d2) #

SuppressUnusedWarnings (Either_Sym2 a6989586621679259290 a6989586621679259291 :: TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym2 a6989586621679259290 a6989586621679259291 :: TyFun (Either a b) c -> Type) (a6989586621679259292 :: Either a b) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym2 a6989586621679259290 a6989586621679259291 :: TyFun (Either a b) c -> Type) (a6989586621679259292 :: Either a b) = Either_ a6989586621679259290 a6989586621679259291 a6989586621679259292

type family Either_Sym3 (a6989586621679259290 :: a ~> c) (a6989586621679259291 :: b ~> c) (a6989586621679259292 :: Either a b) :: c where ... Source #

Equations

Either_Sym3 (a6989586621679259290 :: a ~> c) (a6989586621679259291 :: b ~> c) (a6989586621679259292 :: Either a b) = Either_ a6989586621679259290 a6989586621679259291 a6989586621679259292 

type family LTSym0 :: Ordering where ... Source #

Equations

LTSym0 = 'LT 

type family EQSym0 :: Ordering where ... Source #

Equations

EQSym0 = 'EQ 

type family GTSym0 :: Ordering where ... Source #

Equations

GTSym0 = 'GT 

data (:@#@$) (a1 :: TyFun a ([a] ~> [a])) infixr 5 Source #

Instances

Instances details
SingI ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679050289 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679050289 :: a) = (:@#@$$) a6989586621679050289

data (a6989586621679050289 :: a) :@#@$$ (b :: TyFun [a] [a]) infixr 5 Source #

Instances

Instances details
SingI1 ((:@#@$$) :: a -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((:@#@$$) x) #

SingI d => SingI ((:@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing ((:@#@$$) d) #

SuppressUnusedWarnings ((:@#@$$) a6989586621679050289 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$$) a6989586621679050289 :: TyFun [a] [a] -> Type) (a6989586621679050290 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$$) a6989586621679050289 :: TyFun [a] [a] -> Type) (a6989586621679050290 :: [a]) = a6989586621679050289 ': a6989586621679050290

type family (a6989586621679050289 :: a) :@#@$$$ (a6989586621679050290 :: [a]) :: [a] where ... infixr 5 Source #

Equations

(a6989586621679050289 :: a) :@#@$$$ (a6989586621679050290 :: [a]) = a6989586621679050289 ': a6989586621679050290 

type family NilSym0 :: [a] where ... Source #

Equations

NilSym0 = '[] :: [a] 

Tuples

type family Tuple0Sym0 :: () where ... Source #

Equations

Tuple0Sym0 = '() 

data Tuple2Sym0 (a1 :: TyFun a (b ~> (a, b))) Source #

Instances

Instances details
SingI (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) #

SuppressUnusedWarnings (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679050782 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679050782 :: a) = Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type

data Tuple2Sym1 (a6989586621679050782 :: a) (b1 :: TyFun b (a, b)) Source #

Instances

Instances details
SingI1 (Tuple2Sym1 :: a -> TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple2Sym1 x :: TyFun b (a, b) -> Type) #

SingI d => SingI (Tuple2Sym1 d :: TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple2Sym1 d :: TyFun b (a, b) -> Type) #

SuppressUnusedWarnings (Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type) (a6989586621679050783 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym1 a6989586621679050782 :: TyFun b (a, b) -> Type) (a6989586621679050783 :: b) = '(a6989586621679050782, a6989586621679050783)

type family Tuple2Sym2 (a6989586621679050782 :: a) (a6989586621679050783 :: b) :: (a, b) where ... Source #

Equations

Tuple2Sym2 (a6989586621679050782 :: k1) (a6989586621679050783 :: k2) = '(a6989586621679050782, a6989586621679050783) 

data Tuple3Sym0 (a1 :: TyFun a (b ~> (c ~> (a, b, c)))) Source #

Instances

Instances details
SingI (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) #

SuppressUnusedWarnings (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679050813 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679050813 :: a) = Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type

data Tuple3Sym1 (a6989586621679050813 :: a) (b1 :: TyFun b (c ~> (a, b, c))) Source #

Instances

Instances details
SingI1 (Tuple3Sym1 :: a -> TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple3Sym1 x :: TyFun b (c ~> (a, b, c)) -> Type) #

SingI d => SingI (Tuple3Sym1 d :: TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym1 d :: TyFun b (c ~> (a, b, c)) -> Type) #

SuppressUnusedWarnings (Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679050814 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym1 a6989586621679050813 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679050814 :: b) = Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type

data Tuple3Sym2 (a6989586621679050813 :: a) (a6989586621679050814 :: b) (c1 :: TyFun c (a, b, c)) Source #

Instances

Instances details
SingI2 (Tuple3Sym2 :: a -> b -> TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple3Sym2 x y :: TyFun c (a, b, c) -> Type) #

SingI d => SingI1 (Tuple3Sym2 d :: b -> TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple3Sym2 d x :: TyFun c (a, b, c) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple3Sym2 d1 d2 :: TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple3Sym2 d1 d2 :: TyFun c (a, b, c) -> Type) #

SuppressUnusedWarnings (Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type) (a6989586621679050815 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym2 a6989586621679050813 a6989586621679050814 :: TyFun c (a, b, c) -> Type) (a6989586621679050815 :: c) = '(a6989586621679050813, a6989586621679050814, a6989586621679050815)

type family Tuple3Sym3 (a6989586621679050813 :: a) (a6989586621679050814 :: b) (a6989586621679050815 :: c) :: (a, b, c) where ... Source #

Equations

Tuple3Sym3 (a6989586621679050813 :: k1) (a6989586621679050814 :: k2) (a6989586621679050815 :: k3) = '(a6989586621679050813, a6989586621679050814, a6989586621679050815) 

data Tuple4Sym0 (a1 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d))))) Source #

Instances

Instances details
SingI (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) #

SuppressUnusedWarnings (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679050862 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679050862 :: a) = Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type

data Tuple4Sym1 (a6989586621679050862 :: a) (b1 :: TyFun b (c ~> (d ~> (a, b, c, d)))) Source #

Instances

Instances details
SingI1 (Tuple4Sym1 :: a -> TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple4Sym1 x :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) #

SingI d1 => SingI (Tuple4Sym1 d1 :: TyFun b (c ~> (d2 ~> (a, b, c, d2))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym1 d1 :: TyFun b (c ~> (d2 ~> (a, b, c, d2))) -> Type) #

SuppressUnusedWarnings (Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679050863 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym1 a6989586621679050862 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679050863 :: b) = Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type

data Tuple4Sym2 (a6989586621679050862 :: a) (a6989586621679050863 :: b) (c1 :: TyFun c (d ~> (a, b, c, d))) Source #

Instances

Instances details
SingI2 (Tuple4Sym2 :: a -> b -> TyFun c (d ~> (a, b, c, d)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple4Sym2 x y :: TyFun c (d ~> (a, b, c, d)) -> Type) #

SingI d1 => SingI1 (Tuple4Sym2 d1 :: b -> TyFun c (d2 ~> (a, b, c, d2)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple4Sym2 d1 x :: TyFun c (d2 ~> (a, b, c, d2)) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple4Sym2 d1 d2 :: TyFun c (d3 ~> (a, b, c, d3)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym2 d1 d2 :: TyFun c (d3 ~> (a, b, c, d3)) -> Type) #

SuppressUnusedWarnings (Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679050864 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym2 a6989586621679050862 a6989586621679050863 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679050864 :: c) = Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type

data Tuple4Sym3 (a6989586621679050862 :: a) (a6989586621679050863 :: b) (a6989586621679050864 :: c) (d1 :: TyFun d (a, b, c, d)) Source #

Instances

Instances details
SingI d1 => SingI2 (Tuple4Sym3 d1 :: b -> c -> TyFun d2 (a, b, c, d2) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple4Sym3 d1 x y :: TyFun d2 (a, b, c, d2) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple4Sym3 d1 d2 :: c -> TyFun d3 (a, b, c, d3) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple4Sym3 d1 d2 x :: TyFun d3 (a, b, c, d3) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple4Sym3 d1 d2 d3 :: TyFun d4 (a, b, c, d4) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple4Sym3 d1 d2 d3 :: TyFun d4 (a, b, c, d4) -> Type) #

SuppressUnusedWarnings (Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type) (a6989586621679050865 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym3 a6989586621679050862 a6989586621679050863 a6989586621679050864 :: TyFun d (a, b, c, d) -> Type) (a6989586621679050865 :: d) = '(a6989586621679050862, a6989586621679050863, a6989586621679050864, a6989586621679050865)

type family Tuple4Sym4 (a6989586621679050862 :: a) (a6989586621679050863 :: b) (a6989586621679050864 :: c) (a6989586621679050865 :: d) :: (a, b, c, d) where ... Source #

Equations

Tuple4Sym4 (a6989586621679050862 :: k1) (a6989586621679050863 :: k2) (a6989586621679050864 :: k3) (a6989586621679050865 :: k4) = '(a6989586621679050862, a6989586621679050863, a6989586621679050864, a6989586621679050865) 

data Tuple5Sym0 (a1 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e)))))) Source #

Instances

Instances details
SingI (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) #

SuppressUnusedWarnings (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679050931 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679050931 :: a) = Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type

data Tuple5Sym1 (a6989586621679050931 :: a) (b1 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e))))) Source #

Instances

Instances details
SingI1 (Tuple5Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple5Sym1 x :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) #

SingI d1 => SingI (Tuple5Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (a, b, c, d2, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (a, b, c, d2, e)))) -> Type) #

SuppressUnusedWarnings (Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679050932 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym1 a6989586621679050931 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679050932 :: b) = Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type

data Tuple5Sym2 (a6989586621679050931 :: a) (a6989586621679050932 :: b) (c1 :: TyFun c (d ~> (e ~> (a, b, c, d, e)))) Source #

Instances

Instances details
SingI2 (Tuple5Sym2 :: a -> b -> TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple5Sym2 x y :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) #

SingI d1 => SingI1 (Tuple5Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (a, b, c, d2, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple5Sym2 d1 x :: TyFun c (d2 ~> (e ~> (a, b, c, d2, e))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple5Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (a, b, c, d3, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (a, b, c, d3, e))) -> Type) #

SuppressUnusedWarnings (Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679050933 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym2 a6989586621679050931 a6989586621679050932 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679050933 :: c) = Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type

data Tuple5Sym3 (a6989586621679050931 :: a) (a6989586621679050932 :: b) (a6989586621679050933 :: c) (d1 :: TyFun d (e ~> (a, b, c, d, e))) Source #

Instances

Instances details
SingI d1 => SingI2 (Tuple5Sym3 d1 :: b -> c -> TyFun d2 (e ~> (a, b, c, d2, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple5Sym3 d1 x y :: TyFun d2 (e ~> (a, b, c, d2, e)) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple5Sym3 d1 d2 :: c -> TyFun d3 (e ~> (a, b, c, d3, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple5Sym3 d1 d2 x :: TyFun d3 (e ~> (a, b, c, d3, e)) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple5Sym3 d1 d2 d3 :: TyFun d4 (e ~> (a, b, c, d4, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym3 d1 d2 d3 :: TyFun d4 (e ~> (a, b, c, d4, e)) -> Type) #

SuppressUnusedWarnings (Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679050934 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym3 a6989586621679050931 a6989586621679050932 a6989586621679050933 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679050934 :: d) = Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type

data Tuple5Sym4 (a6989586621679050931 :: a) (a6989586621679050932 :: b) (a6989586621679050933 :: c) (a6989586621679050934 :: d) (e1 :: TyFun e (a, b, c, d, e)) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI2 (Tuple5Sym4 d1 d2 :: c -> d3 -> TyFun e (a, b, c, d3, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple5Sym4 d1 d2 x y :: TyFun e (a, b, c, d3, e) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple5Sym4 d1 d2 d3 :: d4 -> TyFun e (a, b, c, d4, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple5Sym4 d1 d2 d3 x :: TyFun e (a, b, c, d4, e) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple5Sym4 d1 d2 d3 d5 :: TyFun e (a, b, c, d4, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple5Sym4 d1 d2 d3 d5 :: TyFun e (a, b, c, d4, e) -> Type) #

SuppressUnusedWarnings (Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type) (a6989586621679050935 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym4 a6989586621679050931 a6989586621679050932 a6989586621679050933 a6989586621679050934 :: TyFun e (a, b, c, d, e) -> Type) (a6989586621679050935 :: e) = '(a6989586621679050931, a6989586621679050932, a6989586621679050933, a6989586621679050934, a6989586621679050935)

type family Tuple5Sym5 (a6989586621679050931 :: a) (a6989586621679050932 :: b) (a6989586621679050933 :: c) (a6989586621679050934 :: d) (a6989586621679050935 :: e) :: (a, b, c, d, e) where ... Source #

Equations

Tuple5Sym5 (a6989586621679050931 :: k1) (a6989586621679050932 :: k2) (a6989586621679050933 :: k3) (a6989586621679050934 :: k4) (a6989586621679050935 :: k5) = '(a6989586621679050931, a6989586621679050932, a6989586621679050933, a6989586621679050934, a6989586621679050935) 

data Tuple6Sym0 (a1 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))))) Source #

Instances

Instances details
SingI (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) #

SuppressUnusedWarnings (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679051022 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679051022 :: a) = Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type

data Tuple6Sym1 (a6989586621679051022 :: a) (b1 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) Source #

Instances

Instances details
SingI1 (Tuple6Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple6Sym1 x :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) #

SingI d1 => SingI (Tuple6Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f))))) -> Type) #

SuppressUnusedWarnings (Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679051023 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym1 a6989586621679051022 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679051023 :: b) = Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type

data Tuple6Sym2 (a6989586621679051022 :: a) (a6989586621679051023 :: b) (c1 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) Source #

Instances

Instances details
SingI2 (Tuple6Sym2 :: a -> b -> TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple6Sym2 x y :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) #

SingI d1 => SingI1 (Tuple6Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple6Sym2 d1 x :: TyFun c (d2 ~> (e ~> (f ~> (a, b, c, d2, e, f)))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple6Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (a, b, c, d3, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (a, b, c, d3, e, f)))) -> Type) #

SuppressUnusedWarnings (Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679051024 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym2 a6989586621679051022 a6989586621679051023 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679051024 :: c) = Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type

data Tuple6Sym3 (a6989586621679051022 :: a) (a6989586621679051023 :: b) (a6989586621679051024 :: c) (d1 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f)))) Source #

Instances

Instances details
SingI d1 => SingI2 (Tuple6Sym3 d1 :: b -> c -> TyFun d2 (e ~> (f ~> (a, b, c, d2, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple6Sym3 d1 x y :: TyFun d2 (e ~> (f ~> (a, b, c, d2, e, f))) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple6Sym3 d1 d2 :: c -> TyFun d3 (e ~> (f ~> (a, b, c, d3, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple6Sym3 d1 d2 x :: TyFun d3 (e ~> (f ~> (a, b, c, d3, e, f))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple6Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (a, b, c, d4, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (a, b, c, d4, e, f))) -> Type) #

SuppressUnusedWarnings (Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679051025 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym3 a6989586621679051022 a6989586621679051023 a6989586621679051024 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679051025 :: d) = Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type

data Tuple6Sym4 (a6989586621679051022 :: a) (a6989586621679051023 :: b) (a6989586621679051024 :: c) (a6989586621679051025 :: d) (e1 :: TyFun e (f ~> (a, b, c, d, e, f))) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI2 (Tuple6Sym4 d1 d2 :: c -> d3 -> TyFun e (f ~> (a, b, c, d3, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple6Sym4 d1 d2 x y :: TyFun e (f ~> (a, b, c, d3, e, f)) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple6Sym4 d1 d2 d3 :: d4 -> TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple6Sym4 d1 d2 d3 x :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple6Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (a, b, c, d4, e, f)) -> Type) #

SuppressUnusedWarnings (Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679051026 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym4 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679051026 :: e) = Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type

data Tuple6Sym5 (a6989586621679051022 :: a) (a6989586621679051023 :: b) (a6989586621679051024 :: c) (a6989586621679051025 :: d) (a6989586621679051026 :: e) (f1 :: TyFun f (a, b, c, d, e, f)) Source #

Instances

Instances details
(SingI d1, SingI d2, SingI d3) => SingI2 (Tuple6Sym5 d1 d2 d3 :: d4 -> e -> TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: d4) (y :: e). Sing x -> Sing y -> Sing (Tuple6Sym5 d1 d2 d3 x y :: TyFun f (a, b, c, d4, e, f) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI1 (Tuple6Sym5 d1 d2 d3 d5 :: e -> TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: e). Sing x -> Sing (Tuple6Sym5 d1 d2 d3 d5 x :: TyFun f (a, b, c, d4, e, f) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI (Tuple6Sym5 d1 d2 d3 d5 d6 :: TyFun f (a, b, c, d4, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple6Sym5 d1 d2 d3 d5 d6 :: TyFun f (a, b, c, d4, e, f) -> Type) #

SuppressUnusedWarnings (Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type) (a6989586621679051027 :: f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym5 a6989586621679051022 a6989586621679051023 a6989586621679051024 a6989586621679051025 a6989586621679051026 :: TyFun f (a, b, c, d, e, f) -> Type) (a6989586621679051027 :: f) = '(a6989586621679051022, a6989586621679051023, a6989586621679051024, a6989586621679051025, a6989586621679051026, a6989586621679051027)

type family Tuple6Sym6 (a6989586621679051022 :: a) (a6989586621679051023 :: b) (a6989586621679051024 :: c) (a6989586621679051025 :: d) (a6989586621679051026 :: e) (a6989586621679051027 :: f) :: (a, b, c, d, e, f) where ... Source #

Equations

Tuple6Sym6 (a6989586621679051022 :: k1) (a6989586621679051023 :: k2) (a6989586621679051024 :: k3) (a6989586621679051025 :: k4) (a6989586621679051026 :: k5) (a6989586621679051027 :: k6) = '(a6989586621679051022, a6989586621679051023, a6989586621679051024, a6989586621679051025, a6989586621679051026, a6989586621679051027) 

data Tuple7Sym0 (a1 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))))) Source #

Instances

Instances details
SingI (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) #

SuppressUnusedWarnings (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) (a6989586621679051137 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) -> Type) (a6989586621679051137 :: a) = Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type

data Tuple7Sym1 (a6989586621679051137 :: a) (b1 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))))) Source #

Instances

Instances details
SingI1 (Tuple7Sym1 :: a -> TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: a). Sing x -> Sing (Tuple7Sym1 x :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) #

SingI d1 => SingI (Tuple7Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym1 d1 :: TyFun b (c ~> (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))))) -> Type) #

SuppressUnusedWarnings (Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679051138 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym1 a6989586621679051137 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679051138 :: b) = Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type

data Tuple7Sym2 (a6989586621679051137 :: a) (a6989586621679051138 :: b) (c1 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) Source #

Instances

Instances details
SingI2 (Tuple7Sym2 :: a -> b -> TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: a) (y :: b). Sing x -> Sing y -> Sing (Tuple7Sym2 x y :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) #

SingI d1 => SingI1 (Tuple7Sym2 d1 :: b -> TyFun c (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: b). Sing x -> Sing (Tuple7Sym2 d1 x :: TyFun c (d2 ~> (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g))))) -> Type) #

(SingI d1, SingI d2) => SingI (Tuple7Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym2 d1 d2 :: TyFun c (d3 ~> (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g))))) -> Type) #

SuppressUnusedWarnings (Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679051139 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym2 a6989586621679051137 a6989586621679051138 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679051139 :: c) = Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type

data Tuple7Sym3 (a6989586621679051137 :: a) (a6989586621679051138 :: b) (a6989586621679051139 :: c) (d1 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) Source #

Instances

Instances details
SingI d1 => SingI2 (Tuple7Sym3 d1 :: b -> c -> TyFun d2 (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: b) (y :: c). Sing x -> Sing y -> Sing (Tuple7Sym3 d1 x y :: TyFun d2 (e ~> (f ~> (g ~> (a, b, c, d2, e, f, g)))) -> Type) #

(SingI d1, SingI d2) => SingI1 (Tuple7Sym3 d1 d2 :: c -> TyFun d3 (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: c). Sing x -> Sing (Tuple7Sym3 d1 d2 x :: TyFun d3 (e ~> (f ~> (g ~> (a, b, c, d3, e, f, g)))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI (Tuple7Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (g ~> (a, b, c, d4, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym3 d1 d2 d3 :: TyFun d4 (e ~> (f ~> (g ~> (a, b, c, d4, e, f, g)))) -> Type) #

SuppressUnusedWarnings (Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679051140 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym3 a6989586621679051137 a6989586621679051138 a6989586621679051139 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679051140 :: d) = Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type

data Tuple7Sym4 (a6989586621679051137 :: a) (a6989586621679051138 :: b) (a6989586621679051139 :: c) (a6989586621679051140 :: d) (e1 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g)))) Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI2 (Tuple7Sym4 d1 d2 :: c -> d3 -> TyFun e (f ~> (g ~> (a, b, c, d3, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: c) (y :: d3). Sing x -> Sing y -> Sing (Tuple7Sym4 d1 d2 x y :: TyFun e (f ~> (g ~> (a, b, c, d3, e, f, g))) -> Type) #

(SingI d1, SingI d2, SingI d3) => SingI1 (Tuple7Sym4 d1 d2 d3 :: d4 -> TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: d4). Sing x -> Sing (Tuple7Sym4 d1 d2 d3 x :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI (Tuple7Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym4 d1 d2 d3 d5 :: TyFun e (f ~> (g ~> (a, b, c, d4, e, f, g))) -> Type) #

SuppressUnusedWarnings (Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679051141 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym4 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679051141 :: e) = Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type

data Tuple7Sym5 (a6989586621679051137 :: a) (a6989586621679051138 :: b) (a6989586621679051139 :: c) (a6989586621679051140 :: d) (a6989586621679051141 :: e) (f1 :: TyFun f (g ~> (a, b, c, d, e, f, g))) Source #

Instances

Instances details
(SingI d1, SingI d2, SingI d3) => SingI2 (Tuple7Sym5 d1 d2 d3 :: d4 -> e -> TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: d4) (y :: e). Sing x -> Sing y -> Sing (Tuple7Sym5 d1 d2 d3 x y :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5) => SingI1 (Tuple7Sym5 d1 d2 d3 d5 :: e -> TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: e). Sing x -> Sing (Tuple7Sym5 d1 d2 d3 d5 x :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI (Tuple7Sym5 d1 d2 d3 d5 d6 :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym5 d1 d2 d3 d5 d6 :: TyFun f (g ~> (a, b, c, d4, e, f, g)) -> Type) #

SuppressUnusedWarnings (Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679051142 :: f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym5 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679051142 :: f) = Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type

data Tuple7Sym6 (a6989586621679051137 :: a) (a6989586621679051138 :: b) (a6989586621679051139 :: c) (a6989586621679051140 :: d) (a6989586621679051141 :: e) (a6989586621679051142 :: f) (g1 :: TyFun g (a, b, c, d, e, f, g)) Source #

Instances

Instances details
(SingI d1, SingI d2, SingI d3, SingI d5) => SingI2 (Tuple7Sym6 d1 d2 d3 d5 :: e -> f -> TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing2 :: forall (x :: e) (y :: f). Sing x -> Sing y -> Sing (Tuple7Sym6 d1 d2 d3 d5 x y :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6) => SingI1 (Tuple7Sym6 d1 d2 d3 d5 d6 :: f -> TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

liftSing :: forall (x :: f). Sing x -> Sing (Tuple7Sym6 d1 d2 d3 d5 d6 x :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

(SingI d1, SingI d2, SingI d3, SingI d5, SingI d6, SingI d7) => SingI (Tuple7Sym6 d1 d2 d3 d5 d6 d7 :: TyFun g (a, b, c, d4, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing (Tuple7Sym6 d1 d2 d3 d5 d6 d7 :: TyFun g (a, b, c, d4, e, f, g) -> Type) #

SuppressUnusedWarnings (Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type) (a6989586621679051143 :: g) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym6 a6989586621679051137 a6989586621679051138 a6989586621679051139 a6989586621679051140 a6989586621679051141 a6989586621679051142 :: TyFun g (a, b, c, d, e, f, g) -> Type) (a6989586621679051143 :: g) = '(a6989586621679051137, a6989586621679051138, a6989586621679051139, a6989586621679051140, a6989586621679051141, a6989586621679051142, a6989586621679051143)

type family Tuple7Sym7 (a6989586621679051137 :: a) (a6989586621679051138 :: b) (a6989586621679051139 :: c) (a6989586621679051140 :: d) (a6989586621679051141 :: e) (a6989586621679051142 :: f) (a6989586621679051143 :: g) :: (a, b, c, d, e, f, g) where ... Source #

Equations

Tuple7Sym7 (a6989586621679051137 :: k1) (a6989586621679051138 :: k2) (a6989586621679051139 :: k3) (a6989586621679051140 :: k4) (a6989586621679051141 :: k5) (a6989586621679051142 :: k6) (a6989586621679051143 :: k7) = '(a6989586621679051137, a6989586621679051138, a6989586621679051139, a6989586621679051140, a6989586621679051141, a6989586621679051142, a6989586621679051143) 

data FstSym0 (a1 :: TyFun (a, b) a) Source #

Instances

Instances details
SingI (FstSym0 :: TyFun (a, b) a -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (FstSym0 :: TyFun (a, b) a -> Type) #

SuppressUnusedWarnings (FstSym0 :: TyFun (a, b) a -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (FstSym0 :: TyFun (a, b) a -> Type) (a6989586621679147673 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (FstSym0 :: TyFun (a, b) a -> Type) (a6989586621679147673 :: (a, b)) = Fst a6989586621679147673

type family FstSym1 (a6989586621679147673 :: (a, b)) :: a where ... Source #

Equations

FstSym1 (a6989586621679147673 :: (a, b)) = Fst a6989586621679147673 

data SndSym0 (a1 :: TyFun (a, b) b) Source #

Instances

Instances details
SingI (SndSym0 :: TyFun (a, b) b -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (SndSym0 :: TyFun (a, b) b -> Type) #

SuppressUnusedWarnings (SndSym0 :: TyFun (a, b) b -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (SndSym0 :: TyFun (a, b) b -> Type) (a6989586621679147669 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (SndSym0 :: TyFun (a, b) b -> Type) (a6989586621679147669 :: (a, b)) = Snd a6989586621679147669

type family SndSym1 (a6989586621679147669 :: (a, b)) :: b where ... Source #

Equations

SndSym1 (a6989586621679147669 :: (a, b)) = Snd a6989586621679147669 

data CurrySym0 (a1 :: TyFun ((a, b) ~> c) (a ~> (b ~> c))) Source #

Instances

Instances details
SingI (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) #

SuppressUnusedWarnings (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679147661 :: (a, b) ~> c) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679147661 :: (a, b) ~> c) = CurrySym1 a6989586621679147661

data CurrySym1 (a6989586621679147661 :: (a, b) ~> c) (b1 :: TyFun a (b ~> c)) Source #

Instances

Instances details
SingI1 (CurrySym1 :: ((a, b) ~> c) -> TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: (a, b) ~> c). Sing x -> Sing (CurrySym1 x) #

SingI d => SingI (CurrySym1 d :: TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym1 d) #

SuppressUnusedWarnings (CurrySym1 a6989586621679147661 :: TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym1 a6989586621679147661 :: TyFun a (b ~> c) -> Type) (a6989586621679147662 :: a) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym1 a6989586621679147661 :: TyFun a (b ~> c) -> Type) (a6989586621679147662 :: a) = CurrySym2 a6989586621679147661 a6989586621679147662

data CurrySym2 (a6989586621679147661 :: (a, b) ~> c) (a6989586621679147662 :: a) (c1 :: TyFun b c) Source #

Instances

Instances details
SingI d => SingI1 (CurrySym2 d :: a -> TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (CurrySym2 d x) #

SingI2 (CurrySym2 :: ((a, b) ~> c) -> a -> TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing2 :: forall (x :: (a, b) ~> c) (y :: a). Sing x -> Sing y -> Sing (CurrySym2 x y) #

(SingI d1, SingI d2) => SingI (CurrySym2 d1 d2 :: TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (CurrySym2 d1 d2) #

SuppressUnusedWarnings (CurrySym2 a6989586621679147661 a6989586621679147662 :: TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym2 a6989586621679147661 a6989586621679147662 :: TyFun b c -> Type) (a6989586621679147663 :: b) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym2 a6989586621679147661 a6989586621679147662 :: TyFun b c -> Type) (a6989586621679147663 :: b) = Curry a6989586621679147661 a6989586621679147662 a6989586621679147663

type family CurrySym3 (a6989586621679147661 :: (a, b) ~> c) (a6989586621679147662 :: a) (a6989586621679147663 :: b) :: c where ... Source #

Equations

CurrySym3 (a6989586621679147661 :: (a, b) ~> c) (a6989586621679147662 :: a) (a6989586621679147663 :: b) = Curry a6989586621679147661 a6989586621679147662 a6989586621679147663 

data UncurrySym0 (a1 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c)) Source #

Instances

Instances details
SingI (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) #

SuppressUnusedWarnings (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679147653 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679147653 :: a ~> (b ~> c)) = UncurrySym1 a6989586621679147653

data UncurrySym1 (a6989586621679147653 :: a ~> (b ~> c)) (b1 :: TyFun (a, b) c) Source #

Instances

Instances details
SingI1 (UncurrySym1 :: (a ~> (b ~> c)) -> TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (UncurrySym1 x) #

SingI d => SingI (UncurrySym1 d :: TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

Methods

sing :: Sing (UncurrySym1 d) #

SuppressUnusedWarnings (UncurrySym1 a6989586621679147653 :: TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym1 a6989586621679147653 :: TyFun (a, b) c -> Type) (a6989586621679147654 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym1 a6989586621679147653 :: TyFun (a, b) c -> Type) (a6989586621679147654 :: (a, b)) = Uncurry a6989586621679147653 a6989586621679147654

type family UncurrySym2 (a6989586621679147653 :: a ~> (b ~> c)) (a6989586621679147654 :: (a, b)) :: c where ... Source #

Equations

UncurrySym2 (a6989586621679147653 :: a ~> (b ~> c)) (a6989586621679147654 :: (a, b)) = Uncurry a6989586621679147653 a6989586621679147654 

Basic type classes

data (==@#@$) (a1 :: TyFun a (a ~> Bool)) infix 4 Source #

Instances

Instances details
SEq a => SingI ((==@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((==@#@$) :: TyFun a (a ~> Bool) -> Type) #

SuppressUnusedWarnings ((==@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128025 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128025 :: a) = (==@#@$$) a6989586621679128025

data (a6989586621679128025 :: a) ==@#@$$ (b :: TyFun a Bool) infix 4 Source #

Instances

Instances details
SEq a => SingI1 ((==@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((==@#@$$) x) #

(SEq a, SingI d) => SingI ((==@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((==@#@$$) d) #

SuppressUnusedWarnings ((==@#@$$) a6989586621679128025 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$$) a6989586621679128025 :: TyFun a Bool -> Type) (a6989586621679128026 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$$) a6989586621679128025 :: TyFun a Bool -> Type) (a6989586621679128026 :: a) = a6989586621679128025 == a6989586621679128026

type family (a6989586621679128025 :: a) ==@#@$$$ (a6989586621679128026 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679128025 :: a) ==@#@$$$ (a6989586621679128026 :: a) = a6989586621679128025 == a6989586621679128026 

data (/=@#@$) (a1 :: TyFun a (a ~> Bool)) infix 4 Source #

Instances

Instances details
SEq a => SingI ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SuppressUnusedWarnings ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128030 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679128030 :: a) = (/=@#@$$) a6989586621679128030

data (a6989586621679128030 :: a) /=@#@$$ (b :: TyFun a Bool) infix 4 Source #

Instances

Instances details
SEq a => SingI1 ((/=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((/=@#@$$) x) #

(SEq a, SingI d) => SingI ((/=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

sing :: Sing ((/=@#@$$) d) #

SuppressUnusedWarnings ((/=@#@$$) a6989586621679128030 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$$) a6989586621679128030 :: TyFun a Bool -> Type) (a6989586621679128031 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$$) a6989586621679128030 :: TyFun a Bool -> Type) (a6989586621679128031 :: a) = a6989586621679128030 /= a6989586621679128031

type family (a6989586621679128030 :: a) /=@#@$$$ (a6989586621679128031 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679128030 :: a) /=@#@$$$ (a6989586621679128031 :: a) = a6989586621679128030 /= a6989586621679128031 

data CompareSym0 (a1 :: TyFun a (a ~> Ordering)) Source #

Instances

Instances details
SOrd a => SingI (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) #

SuppressUnusedWarnings (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679189966 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679189966 :: a) = CompareSym1 a6989586621679189966

data CompareSym1 (a6989586621679189966 :: a) (b :: TyFun a Ordering) Source #

Instances

Instances details
SOrd a => SingI1 (CompareSym1 :: a -> TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (CompareSym1 x) #

(SOrd a, SingI d) => SingI (CompareSym1 d :: TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (CompareSym1 d) #

SuppressUnusedWarnings (CompareSym1 a6989586621679189966 :: TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym1 a6989586621679189966 :: TyFun a Ordering -> Type) (a6989586621679189967 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym1 a6989586621679189966 :: TyFun a Ordering -> Type) (a6989586621679189967 :: a) = Compare a6989586621679189966 a6989586621679189967

type family CompareSym2 (a6989586621679189966 :: a) (a6989586621679189967 :: a) :: Ordering where ... Source #

Equations

CompareSym2 (a6989586621679189966 :: a) (a6989586621679189967 :: a) = Compare a6989586621679189966 a6989586621679189967 

data (<@#@$) (a1 :: TyFun a (a ~> Bool)) infix 4 Source #

Instances

Instances details
SOrd a => SingI ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<@#@$) :: TyFun a (a ~> Bool) -> Type) #

SuppressUnusedWarnings ((<@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189971 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189971 :: a) = (<@#@$$) a6989586621679189971

data (a6989586621679189971 :: a) <@#@$$ (b :: TyFun a Bool) infix 4 Source #

Instances

Instances details
SOrd a => SingI1 ((<@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<@#@$$) x) #

(SOrd a, SingI d) => SingI ((<@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<@#@$$) d) #

SuppressUnusedWarnings ((<@#@$$) a6989586621679189971 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$$) a6989586621679189971 :: TyFun a Bool -> Type) (a6989586621679189972 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$$) a6989586621679189971 :: TyFun a Bool -> Type) (a6989586621679189972 :: a) = a6989586621679189971 < a6989586621679189972

type family (a6989586621679189971 :: a) <@#@$$$ (a6989586621679189972 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679189971 :: a) <@#@$$$ (a6989586621679189972 :: a) = a6989586621679189971 < a6989586621679189972 

data (<=@#@$) (a1 :: TyFun a (a ~> Bool)) infix 4 Source #

Instances

Instances details
SOrd a => SingI ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SuppressUnusedWarnings ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189976 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189976 :: a) = (<=@#@$$) a6989586621679189976

data (a6989586621679189976 :: a) <=@#@$$ (b :: TyFun a Bool) infix 4 Source #

Instances

Instances details
SOrd a => SingI1 ((<=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<=@#@$$) x) #

(SOrd a, SingI d) => SingI ((<=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((<=@#@$$) d) #

SuppressUnusedWarnings ((<=@#@$$) a6989586621679189976 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$$) a6989586621679189976 :: TyFun a Bool -> Type) (a6989586621679189977 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$$) a6989586621679189976 :: TyFun a Bool -> Type) (a6989586621679189977 :: a) = a6989586621679189976 <= a6989586621679189977

type family (a6989586621679189976 :: a) <=@#@$$$ (a6989586621679189977 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679189976 :: a) <=@#@$$$ (a6989586621679189977 :: a) = a6989586621679189976 <= a6989586621679189977 

data (>@#@$) (a1 :: TyFun a (a ~> Bool)) infix 4 Source #

Instances

Instances details
SOrd a => SingI ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>@#@$) :: TyFun a (a ~> Bool) -> Type) #

SuppressUnusedWarnings ((>@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189981 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189981 :: a) = (>@#@$$) a6989586621679189981

data (a6989586621679189981 :: a) >@#@$$ (b :: TyFun a Bool) infix 4 Source #

Instances

Instances details
SOrd a => SingI1 ((>@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((>@#@$$) x) #

(SOrd a, SingI d) => SingI ((>@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>@#@$$) d) #

SuppressUnusedWarnings ((>@#@$$) a6989586621679189981 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$$) a6989586621679189981 :: TyFun a Bool -> Type) (a6989586621679189982 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$$) a6989586621679189981 :: TyFun a Bool -> Type) (a6989586621679189982 :: a) = a6989586621679189981 > a6989586621679189982

type family (a6989586621679189981 :: a) >@#@$$$ (a6989586621679189982 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679189981 :: a) >@#@$$$ (a6989586621679189982 :: a) = a6989586621679189981 > a6989586621679189982 

data (>=@#@$) (a1 :: TyFun a (a ~> Bool)) infix 4 Source #

Instances

Instances details
SOrd a => SingI ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) #

SuppressUnusedWarnings ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189986 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679189986 :: a) = (>=@#@$$) a6989586621679189986

data (a6989586621679189986 :: a) >=@#@$$ (b :: TyFun a Bool) infix 4 Source #

Instances

Instances details
SOrd a => SingI1 ((>=@#@$$) :: a -> TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((>=@#@$$) x) #

(SOrd a, SingI d) => SingI ((>=@#@$$) d :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing ((>=@#@$$) d) #

SuppressUnusedWarnings ((>=@#@$$) a6989586621679189986 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$$) a6989586621679189986 :: TyFun a Bool -> Type) (a6989586621679189987 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$$) a6989586621679189986 :: TyFun a Bool -> Type) (a6989586621679189987 :: a) = a6989586621679189986 >= a6989586621679189987

type family (a6989586621679189986 :: a) >=@#@$$$ (a6989586621679189987 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679189986 :: a) >=@#@$$$ (a6989586621679189987 :: a) = a6989586621679189986 >= a6989586621679189987 

data MaxSym0 (a1 :: TyFun a (a ~> a)) Source #

Instances

Instances details
SOrd a => SingI (MaxSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MaxSym0 :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings (MaxSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189991 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189991 :: a) = MaxSym1 a6989586621679189991

data MaxSym1 (a6989586621679189991 :: a) (b :: TyFun a a) Source #

Instances

Instances details
SOrd a => SingI1 (MaxSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MaxSym1 x) #

(SOrd a, SingI d) => SingI (MaxSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MaxSym1 d) #

SuppressUnusedWarnings (MaxSym1 a6989586621679189991 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym1 a6989586621679189991 :: TyFun a a -> Type) (a6989586621679189992 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym1 a6989586621679189991 :: TyFun a a -> Type) (a6989586621679189992 :: a) = Max a6989586621679189991 a6989586621679189992

type family MaxSym2 (a6989586621679189991 :: a) (a6989586621679189992 :: a) :: a where ... Source #

Equations

MaxSym2 (a6989586621679189991 :: a) (a6989586621679189992 :: a) = Max a6989586621679189991 a6989586621679189992 

data MinSym0 (a1 :: TyFun a (a ~> a)) Source #

Instances

Instances details
SOrd a => SingI (MinSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MinSym0 :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings (MinSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189996 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679189996 :: a) = MinSym1 a6989586621679189996

data MinSym1 (a6989586621679189996 :: a) (b :: TyFun a a) Source #

Instances

Instances details
SOrd a => SingI1 (MinSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MinSym1 x) #

(SOrd a, SingI d) => SingI (MinSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sing :: Sing (MinSym1 d) #

SuppressUnusedWarnings (MinSym1 a6989586621679189996 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym1 a6989586621679189996 :: TyFun a a -> Type) (a6989586621679189997 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym1 a6989586621679189996 :: TyFun a a -> Type) (a6989586621679189997 :: a) = Min a6989586621679189996 a6989586621679189997

type family MinSym2 (a6989586621679189996 :: a) (a6989586621679189997 :: a) :: a where ... Source #

Equations

MinSym2 (a6989586621679189996 :: a) (a6989586621679189997 :: a) = Min a6989586621679189996 a6989586621679189997 

data ToEnumSym0 (a1 :: TyFun Natural a) Source #

Instances

Instances details
SEnum a => SingI (ToEnumSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (ToEnumSym0 :: TyFun Natural a -> Type) #

SuppressUnusedWarnings (ToEnumSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (ToEnumSym0 :: TyFun Natural a -> Type) (a6989586621679414060 :: Natural) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (ToEnumSym0 :: TyFun Natural a -> Type) (a6989586621679414060 :: Natural) = ToEnum a6989586621679414060 :: a

type family ToEnumSym1 (a6989586621679414060 :: Natural) :: a where ... Source #

Equations

ToEnumSym1 a6989586621679414060 = ToEnum a6989586621679414060 :: a 

data FromEnumSym0 (a1 :: TyFun a Natural) Source #

Instances

Instances details
SEnum a => SingI (FromEnumSym0 :: TyFun a Natural -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (FromEnumSym0 :: TyFun a Natural -> Type) #

SuppressUnusedWarnings (FromEnumSym0 :: TyFun a Natural -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (FromEnumSym0 :: TyFun a Natural -> Type) (a6989586621679414063 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (FromEnumSym0 :: TyFun a Natural -> Type) (a6989586621679414063 :: a) = FromEnum a6989586621679414063

type family FromEnumSym1 (a6989586621679414063 :: a) :: Natural where ... Source #

Equations

FromEnumSym1 (a6989586621679414063 :: a) = FromEnum a6989586621679414063 

data EnumFromToSym0 (a1 :: TyFun a (a ~> [a])) Source #

Instances

Instances details
SEnum a => SingI (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) #

SuppressUnusedWarnings (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414067 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414067 :: a) = EnumFromToSym1 a6989586621679414067

data EnumFromToSym1 (a6989586621679414067 :: a) (b :: TyFun a [a]) Source #

Instances

Instances details
SEnum a => SingI1 (EnumFromToSym1 :: a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromToSym1 x) #

(SEnum a, SingI d) => SingI (EnumFromToSym1 d :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromToSym1 d) #

SuppressUnusedWarnings (EnumFromToSym1 a6989586621679414067 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym1 a6989586621679414067 :: TyFun a [a] -> Type) (a6989586621679414068 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym1 a6989586621679414067 :: TyFun a [a] -> Type) (a6989586621679414068 :: a) = EnumFromTo a6989586621679414067 a6989586621679414068

type family EnumFromToSym2 (a6989586621679414067 :: a) (a6989586621679414068 :: a) :: [a] where ... Source #

Equations

EnumFromToSym2 (a6989586621679414067 :: a) (a6989586621679414068 :: a) = EnumFromTo a6989586621679414067 a6989586621679414068 

data EnumFromThenToSym0 (a1 :: TyFun a (a ~> (a ~> [a]))) Source #

Instances

Instances details
SEnum a => SingI (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) #

SuppressUnusedWarnings (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679414073 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679414073 :: a) = EnumFromThenToSym1 a6989586621679414073

data EnumFromThenToSym1 (a6989586621679414073 :: a) (b :: TyFun a (a ~> [a])) Source #

Instances

Instances details
SEnum a => SingI1 (EnumFromThenToSym1 :: a -> TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromThenToSym1 x) #

(SEnum a, SingI d) => SingI (EnumFromThenToSym1 d :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (EnumFromThenToSym1 a6989586621679414073 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679414073 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414074 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679414073 :: TyFun a (a ~> [a]) -> Type) (a6989586621679414074 :: a) = EnumFromThenToSym2 a6989586621679414073 a6989586621679414074

data EnumFromThenToSym2 (a6989586621679414073 :: a) (a6989586621679414074 :: a) (c :: TyFun a [a]) Source #

Instances

Instances details
SEnum a => SingI2 (EnumFromThenToSym2 :: a -> a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing2 :: forall (x :: a) (y :: a). Sing x -> Sing y -> Sing (EnumFromThenToSym2 x y) #

(SEnum a, SingI d) => SingI1 (EnumFromThenToSym2 d :: a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: a). Sing x -> Sing (EnumFromThenToSym2 d x) #

(SEnum a, SingI d1, SingI d2) => SingI (EnumFromThenToSym2 d1 d2 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromThenToSym2 d1 d2) #

SuppressUnusedWarnings (EnumFromThenToSym2 a6989586621679414073 a6989586621679414074 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym2 a6989586621679414073 a6989586621679414074 :: TyFun a [a] -> Type) (a6989586621679414075 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym2 a6989586621679414073 a6989586621679414074 :: TyFun a [a] -> Type) (a6989586621679414075 :: a) = EnumFromThenTo a6989586621679414073 a6989586621679414074 a6989586621679414075

type family EnumFromThenToSym3 (a6989586621679414073 :: a) (a6989586621679414074 :: a) (a6989586621679414075 :: a) :: [a] where ... Source #

Equations

EnumFromThenToSym3 (a6989586621679414073 :: a) (a6989586621679414074 :: a) (a6989586621679414075 :: a) = EnumFromThenTo a6989586621679414073 a6989586621679414074 a6989586621679414075 

type family MinBoundSym0 :: a where ... Source #

Equations

MinBoundSym0 = MinBound :: a 

type family MaxBoundSym0 :: a where ... Source #

Equations

MaxBoundSym0 = MaxBound :: a 

Numbers

Numeric type classes

data (+@#@$) (a1 :: TyFun a (a ~> a)) infixl 6 Source #

Instances

Instances details
SNum a => SingI ((+@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((+@#@$) :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings ((+@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398568 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398568 :: a) = (+@#@$$) a6989586621679398568

data (a6989586621679398568 :: a) +@#@$$ (b :: TyFun a a) infixl 6 Source #

Instances

Instances details
SNum a => SingI1 ((+@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((+@#@$$) x) #

(SNum a, SingI d) => SingI ((+@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((+@#@$$) d) #

SuppressUnusedWarnings ((+@#@$$) a6989586621679398568 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$$) a6989586621679398568 :: TyFun a a -> Type) (a6989586621679398569 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$$) a6989586621679398568 :: TyFun a a -> Type) (a6989586621679398569 :: a) = a6989586621679398568 + a6989586621679398569

type family (a6989586621679398568 :: a) +@#@$$$ (a6989586621679398569 :: a) :: a where ... infixl 6 Source #

Equations

(a6989586621679398568 :: a) +@#@$$$ (a6989586621679398569 :: a) = a6989586621679398568 + a6989586621679398569 

data (-@#@$) (a1 :: TyFun a (a ~> a)) infixl 6 Source #

Instances

Instances details
SNum a => SingI ((-@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((-@#@$) :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings ((-@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398573 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398573 :: a) = (-@#@$$) a6989586621679398573

data (a6989586621679398573 :: a) -@#@$$ (b :: TyFun a a) infixl 6 Source #

Instances

Instances details
SNum a => SingI1 ((-@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((-@#@$$) x) #

(SNum a, SingI d) => SingI ((-@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((-@#@$$) d) #

SuppressUnusedWarnings ((-@#@$$) a6989586621679398573 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$$) a6989586621679398573 :: TyFun a a -> Type) (a6989586621679398574 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$$) a6989586621679398573 :: TyFun a a -> Type) (a6989586621679398574 :: a) = a6989586621679398573 - a6989586621679398574

type family (a6989586621679398573 :: a) -@#@$$$ (a6989586621679398574 :: a) :: a where ... infixl 6 Source #

Equations

(a6989586621679398573 :: a) -@#@$$$ (a6989586621679398574 :: a) = a6989586621679398573 - a6989586621679398574 

data (*@#@$) (a1 :: TyFun a (a ~> a)) infixl 7 Source #

Instances

Instances details
SNum a => SingI ((*@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((*@#@$) :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings ((*@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398578 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679398578 :: a) = (*@#@$$) a6989586621679398578

data (a6989586621679398578 :: a) *@#@$$ (b :: TyFun a a) infixl 7 Source #

Instances

Instances details
SNum a => SingI1 ((*@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((*@#@$$) x) #

(SNum a, SingI d) => SingI ((*@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing ((*@#@$$) d) #

SuppressUnusedWarnings ((*@#@$$) a6989586621679398578 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$$) a6989586621679398578 :: TyFun a a -> Type) (a6989586621679398579 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$$) a6989586621679398578 :: TyFun a a -> Type) (a6989586621679398579 :: a) = a6989586621679398578 * a6989586621679398579

type family (a6989586621679398578 :: a) *@#@$$$ (a6989586621679398579 :: a) :: a where ... infixl 7 Source #

Equations

(a6989586621679398578 :: a) *@#@$$$ (a6989586621679398579 :: a) = a6989586621679398578 * a6989586621679398579 

data NegateSym0 (a1 :: TyFun a a) Source #

Instances

Instances details
SNum a => SingI (NegateSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (NegateSym0 :: TyFun a a -> Type) #

SuppressUnusedWarnings (NegateSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679398582 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679398582 :: a) = Negate a6989586621679398582

type family NegateSym1 (a6989586621679398582 :: a) :: a where ... Source #

Equations

NegateSym1 (a6989586621679398582 :: a) = Negate a6989586621679398582 

data AbsSym0 (a1 :: TyFun a a) Source #

Instances

Instances details
SNum a => SingI (AbsSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (AbsSym0 :: TyFun a a -> Type) #

SuppressUnusedWarnings (AbsSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (AbsSym0 :: TyFun a a -> Type) (a6989586621679398585 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (AbsSym0 :: TyFun a a -> Type) (a6989586621679398585 :: a) = Abs a6989586621679398585

type family AbsSym1 (a6989586621679398585 :: a) :: a where ... Source #

Equations

AbsSym1 (a6989586621679398585 :: a) = Abs a6989586621679398585 

data SignumSym0 (a1 :: TyFun a a) Source #

Instances

Instances details
SNum a => SingI (SignumSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SignumSym0 :: TyFun a a -> Type) #

SuppressUnusedWarnings (SignumSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679398588 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679398588 :: a) = Signum a6989586621679398588

type family SignumSym1 (a6989586621679398588 :: a) :: a where ... Source #

Equations

SignumSym1 (a6989586621679398588 :: a) = Signum a6989586621679398588 

data FromIntegerSym0 (a1 :: TyFun Natural a) Source #

Instances

Instances details
SNum a => SingI (FromIntegerSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (FromIntegerSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (FromIntegerSym0 :: TyFun Natural a -> Type) (a6989586621679398591 :: Natural) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (FromIntegerSym0 :: TyFun Natural a -> Type) (a6989586621679398591 :: Natural) = FromInteger a6989586621679398591 :: a

type family FromIntegerSym1 (a6989586621679398591 :: Natural) :: a where ... Source #

Equations

FromIntegerSym1 a6989586621679398591 = FromInteger a6989586621679398591 :: a 

Numeric functions

data SubtractSym0 (a1 :: TyFun a (a ~> a)) Source #

Instances

Instances details
SNum a => SingI (SubtractSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SubtractSym0 :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings (SubtractSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679398561 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679398561 :: a) = SubtractSym1 a6989586621679398561

data SubtractSym1 (a6989586621679398561 :: a) (b :: TyFun a a) Source #

Instances

Instances details
SNum a => SingI1 (SubtractSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (SubtractSym1 x) #

(SNum a, SingI d) => SingI (SubtractSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

Methods

sing :: Sing (SubtractSym1 d) #

SuppressUnusedWarnings (SubtractSym1 a6989586621679398561 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym1 a6989586621679398561 :: TyFun a a -> Type) (a6989586621679398562 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym1 a6989586621679398561 :: TyFun a a -> Type) (a6989586621679398562 :: a) = Subtract a6989586621679398561 a6989586621679398562

type family SubtractSym2 (a6989586621679398561 :: a) (a6989586621679398562 :: a) :: a where ... Source #

Equations

SubtractSym2 (a6989586621679398561 :: a) (a6989586621679398562 :: a) = Subtract a6989586621679398561 a6989586621679398562 

Semigroups and Monoids

data (<>@#@$) (a1 :: TyFun a (a ~> a)) infixr 6 Source #

Instances

Instances details
SSemigroup a => SingI ((<>@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing ((<>@#@$) :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings ((<>@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679173979 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679173979 :: a) = (<>@#@$$) a6989586621679173979

data (a6989586621679173979 :: a) <>@#@$$ (b :: TyFun a a) infixr 6 Source #

Instances

Instances details
SSemigroup a => SingI1 ((<>@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<>@#@$$) x) #

(SSemigroup a, SingI d) => SingI ((<>@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing ((<>@#@$$) d) #

SuppressUnusedWarnings ((<>@#@$$) a6989586621679173979 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$$) a6989586621679173979 :: TyFun a a -> Type) (a6989586621679173980 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$$) a6989586621679173979 :: TyFun a a -> Type) (a6989586621679173980 :: a) = a6989586621679173979 <> a6989586621679173980

type family (a6989586621679173979 :: a) <>@#@$$$ (a6989586621679173980 :: a) :: a where ... infixr 6 Source #

Equations

(a6989586621679173979 :: a) <>@#@$$$ (a6989586621679173980 :: a) = a6989586621679173979 <> a6989586621679173980 

type family MemptySym0 :: a where ... Source #

Equations

MemptySym0 = Mempty :: a 

data MappendSym0 (a1 :: TyFun a (a ~> a)) Source #

Instances

Instances details
SMonoid a => SingI (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MappendSym0 :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679860746 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679860746 :: a) = MappendSym1 a6989586621679860746

data MappendSym1 (a6989586621679860746 :: a) (b :: TyFun a a) Source #

Instances

Instances details
SMonoid a => SingI1 (MappendSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (MappendSym1 x) #

(SMonoid a, SingI d) => SingI (MappendSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MappendSym1 d) #

SuppressUnusedWarnings (MappendSym1 a6989586621679860746 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym1 a6989586621679860746 :: TyFun a a -> Type) (a6989586621679860747 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym1 a6989586621679860746 :: TyFun a a -> Type) (a6989586621679860747 :: a) = Mappend a6989586621679860746 a6989586621679860747

type family MappendSym2 (a6989586621679860746 :: a) (a6989586621679860747 :: a) :: a where ... Source #

Equations

MappendSym2 (a6989586621679860746 :: a) (a6989586621679860747 :: a) = Mappend a6989586621679860746 a6989586621679860747 

data MconcatSym0 (a1 :: TyFun [a] a) Source #

Instances

Instances details
SMonoid a => SingI (MconcatSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MconcatSym0 :: TyFun [a] a -> Type) #

SuppressUnusedWarnings (MconcatSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621679860750 :: [a]) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621679860750 :: [a]) = Mconcat a6989586621679860750

type family MconcatSym1 (a6989586621679860750 :: [a]) :: a where ... Source #

Equations

MconcatSym1 (a6989586621679860750 :: [a]) = Mconcat a6989586621679860750 

Monads and functors

data FmapSym0 (a1 :: TyFun (a ~> b) (f a ~> f b)) Source #

Instances

Instances details
SFunctor f => SingI (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SuppressUnusedWarnings (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271227 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679271227 :: a ~> b) = FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type

data FmapSym1 (a6989586621679271227 :: a ~> b) (b1 :: TyFun (f a) (f b)) Source #

Instances

Instances details
SFunctor f => SingI1 (FmapSym1 :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (FmapSym1 x :: TyFun (f a) (f b) -> Type) #

(SFunctor f, SingI d) => SingI (FmapSym1 d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (FmapSym1 d :: TyFun (f a) (f b) -> Type) #

SuppressUnusedWarnings (FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type) (a6989586621679271228 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym1 a6989586621679271227 :: TyFun (f a) (f b) -> Type) (a6989586621679271228 :: f a) = Fmap a6989586621679271227 a6989586621679271228

type family FmapSym2 (a6989586621679271227 :: a ~> b) (a6989586621679271228 :: f a) :: f b where ... Source #

Equations

FmapSym2 (a6989586621679271227 :: a ~> b) (a6989586621679271228 :: f a) = Fmap a6989586621679271227 a6989586621679271228 

data (<$@#@$) (a1 :: TyFun a (f b ~> f a)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) #

SuppressUnusedWarnings ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679271232 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679271232 :: a) = (<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type

data (a6989586621679271232 :: a) <$@#@$$ (b1 :: TyFun (f b) (f a)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI1 ((<$@#@$$) :: a -> TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<$@#@$$) x :: TyFun (f b) (f a) -> Type) #

(SFunctor f, SingI d) => SingI ((<$@#@$$) d :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<$@#@$$) d :: TyFun (f b) (f a) -> Type) #

SuppressUnusedWarnings ((<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type) (a6989586621679271233 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$$) a6989586621679271232 :: TyFun (f b) (f a) -> Type) (a6989586621679271233 :: f b) = a6989586621679271232 <$ a6989586621679271233

type family (a6989586621679271232 :: a) <$@#@$$$ (a6989586621679271233 :: f b) :: f a where ... infixl 4 Source #

Equations

(a6989586621679271232 :: a) <$@#@$$$ (a6989586621679271233 :: f b) = a6989586621679271232 <$ a6989586621679271233 

data (<$>@#@$) (a1 :: TyFun (a ~> b) (f a ~> f b)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) #

SuppressUnusedWarnings ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679357520 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679357520 :: a ~> b) = (<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type

data (a6989586621679357520 :: a ~> b) <$>@#@$$ (b1 :: TyFun (f a) (f b)) infixl 4 Source #

Instances

Instances details
SFunctor f => SingI1 ((<$>@#@$$) :: (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing ((<$>@#@$$) x :: TyFun (f a) (f b) -> Type) #

(SFunctor f, SingI d) => SingI ((<$>@#@$$) d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

Methods

sing :: Sing ((<$>@#@$$) d :: TyFun (f a) (f b) -> Type) #

SuppressUnusedWarnings ((<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type) (a6989586621679357521 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$$) a6989586621679357520 :: TyFun (f a) (f b) -> Type) (a6989586621679357521 :: f a) = a6989586621679357520 <$> a6989586621679357521

type family (a6989586621679357520 :: a ~> b) <$>@#@$$$ (a6989586621679357521 :: f a) :: f b where ... infixl 4 Source #

Equations

(a6989586621679357520 :: a ~> b) <$>@#@$$$ (a6989586621679357521 :: f a) = a6989586621679357520 <$> a6989586621679357521 

data PureSym0 (a1 :: TyFun a (f a)) Source #

Instances

Instances details
SApplicative f => SingI (PureSym0 :: TyFun a (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (PureSym0 :: TyFun a (f a) -> Type) #

SuppressUnusedWarnings (PureSym0 :: TyFun a (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (PureSym0 :: TyFun a (f a) -> Type) (a6989586621679271251 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (PureSym0 :: TyFun a (f a) -> Type) (a6989586621679271251 :: a) = Pure a6989586621679271251 :: f a

type family PureSym1 (a6989586621679271251 :: a) :: f a where ... Source #

Equations

PureSym1 (a6989586621679271251 :: a) = Pure a6989586621679271251 :: f a 

data (<*>@#@$) (a1 :: TyFun (f (a ~> b)) (f a ~> f b)) infixl 4 Source #

Instances

Instances details
SApplicative f => SingI ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) #

SuppressUnusedWarnings ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679271255 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679271255 :: f (a ~> b)) = (<*>@#@$$) a6989586621679271255

data (a6989586621679271255 :: f (a ~> b)) <*>@#@$$ (b1 :: TyFun (f a) (f b)) infixl 4 Source #

Instances

Instances details
SApplicative f => SingI1 ((<*>@#@$$) :: f (a ~> b) -> TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f (a ~> b)). Sing x -> Sing ((<*>@#@$$) x) #

(SApplicative f, SingI d) => SingI ((<*>@#@$$) d :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*>@#@$$) d) #

SuppressUnusedWarnings ((<*>@#@$$) a6989586621679271255 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$$) a6989586621679271255 :: TyFun (f a) (f b) -> Type) (a6989586621679271256 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$$) a6989586621679271255 :: TyFun (f a) (f b) -> Type) (a6989586621679271256 :: f a) = a6989586621679271255 <*> a6989586621679271256

type family (a6989586621679271255 :: f (a ~> b)) <*>@#@$$$ (a6989586621679271256 :: f a) :: f b where ... infixl 4 Source #

Equations

(a6989586621679271255 :: f (a ~> b)) <*>@#@$$$ (a6989586621679271256 :: f a) = a6989586621679271255 <*> a6989586621679271256 

data (*>@#@$) (a1 :: TyFun (f a) (f b ~> f b)) infixl 4 Source #

Instances

Instances details
SApplicative f => SingI ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) #

SuppressUnusedWarnings ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679271267 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679271267 :: f a) = (*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type

data (a6989586621679271267 :: f a) *>@#@$$ (b1 :: TyFun (f b) (f b)) infixl 4 Source #

Instances

Instances details
SApplicative f => SingI1 ((*>@#@$$) :: f a -> TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((*>@#@$$) x :: TyFun (f b) (f b) -> Type) #

(SApplicative f, SingI d) => SingI ((*>@#@$$) d :: TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((*>@#@$$) d :: TyFun (f b) (f b) -> Type) #

SuppressUnusedWarnings ((*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type) (a6989586621679271268 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$$) a6989586621679271267 :: TyFun (f b) (f b) -> Type) (a6989586621679271268 :: f b) = a6989586621679271267 *> a6989586621679271268

type family (a6989586621679271267 :: f a) *>@#@$$$ (a6989586621679271268 :: f b) :: f b where ... infixl 4 Source #

Equations

(a6989586621679271267 :: f a) *>@#@$$$ (a6989586621679271268 :: f b) = a6989586621679271267 *> a6989586621679271268 

data (<*@#@$) (a1 :: TyFun (f a) (f b ~> f a)) infixl 4 Source #

Instances

Instances details
SApplicative f => SingI ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) #

SuppressUnusedWarnings ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679271272 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679271272 :: f a) = (<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type

data (a6989586621679271272 :: f a) <*@#@$$ (b1 :: TyFun (f b) (f a)) infixl 4 Source #

Instances

Instances details
SApplicative f => SingI1 ((<*@#@$$) :: f a -> TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing ((<*@#@$$) x :: TyFun (f b) (f a) -> Type) #

(SApplicative f, SingI d) => SingI ((<*@#@$$) d :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((<*@#@$$) d :: TyFun (f b) (f a) -> Type) #

SuppressUnusedWarnings ((<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type) (a6989586621679271273 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$$) a6989586621679271272 :: TyFun (f b) (f a) -> Type) (a6989586621679271273 :: f b) = a6989586621679271272 <* a6989586621679271273

type family (a6989586621679271272 :: f a) <*@#@$$$ (a6989586621679271273 :: f b) :: f a where ... infixl 4 Source #

Equations

(a6989586621679271272 :: f a) <*@#@$$$ (a6989586621679271273 :: f b) = a6989586621679271272 <* a6989586621679271273 

data LiftA2Sym0 (a1 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c))) Source #

Instances

Instances details
SApplicative f => SingI (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) #

SuppressUnusedWarnings (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679271261 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679271261 :: a ~> (b ~> c)) = LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type

data LiftA2Sym1 (a6989586621679271261 :: a ~> (b ~> c)) (b1 :: TyFun (f a) (f b ~> f c)) Source #

Instances

Instances details
SApplicative f => SingI1 (LiftA2Sym1 :: (a ~> (b ~> c)) -> TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (LiftA2Sym1 x :: TyFun (f a) (f b ~> f c) -> Type) #

(SApplicative f, SingI d) => SingI (LiftA2Sym1 d :: TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym1 d :: TyFun (f a) (f b ~> f c) -> Type) #

SuppressUnusedWarnings (LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679271262 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym1 a6989586621679271261 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679271262 :: f a) = LiftA2Sym2 a6989586621679271261 a6989586621679271262

data LiftA2Sym2 (a6989586621679271261 :: a ~> (b ~> c)) (a6989586621679271262 :: f a) (c1 :: TyFun (f b) (f c)) Source #

Instances

Instances details
(SApplicative f, SingI d) => SingI1 (LiftA2Sym2 d :: f a -> TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: f a). Sing x -> Sing (LiftA2Sym2 d x) #

SApplicative f => SingI2 (LiftA2Sym2 :: (a ~> (b ~> c)) -> f a -> TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: f a). Sing x -> Sing y -> Sing (LiftA2Sym2 x y) #

(SApplicative f, SingI d1, SingI d2) => SingI (LiftA2Sym2 d1 d2 :: TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (LiftA2Sym2 d1 d2) #

SuppressUnusedWarnings (LiftA2Sym2 a6989586621679271261 a6989586621679271262 :: TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym2 a6989586621679271261 a6989586621679271262 :: TyFun (f b) (f c) -> Type) (a6989586621679271263 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym2 a6989586621679271261 a6989586621679271262 :: TyFun (f b) (f c) -> Type) (a6989586621679271263 :: f b) = LiftA2 a6989586621679271261 a6989586621679271262 a6989586621679271263

type family LiftA2Sym3 (a6989586621679271261 :: a ~> (b ~> c)) (a6989586621679271262 :: f a) (a6989586621679271263 :: f b) :: f c where ... Source #

Equations

LiftA2Sym3 (a6989586621679271261 :: a ~> (b ~> c)) (a6989586621679271262 :: f a) (a6989586621679271263 :: f b) = LiftA2 a6989586621679271261 a6989586621679271262 a6989586621679271263 

data (>>=@#@$) (a1 :: TyFun (m a) ((a ~> m b) ~> m b)) infixl 1 Source #

Instances

Instances details
SMonad m => SingI ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) #

SuppressUnusedWarnings ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679271335 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679271335 :: m a) = (>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type

data (a6989586621679271335 :: m a) >>=@#@$$ (b1 :: TyFun (a ~> m b) (m b)) infixl 1 Source #

Instances

Instances details
SMonad m => SingI1 ((>>=@#@$$) :: m a -> TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a). Sing x -> Sing ((>>=@#@$$) x :: TyFun (a ~> m b) (m b) -> Type) #

(SMonad m, SingI d) => SingI ((>>=@#@$$) d :: TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>=@#@$$) d :: TyFun (a ~> m b) (m b) -> Type) #

SuppressUnusedWarnings ((>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679271336 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$$) a6989586621679271335 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679271336 :: a ~> m b) = a6989586621679271335 >>= a6989586621679271336

type family (a6989586621679271335 :: m a) >>=@#@$$$ (a6989586621679271336 :: a ~> m b) :: m b where ... infixl 1 Source #

Equations

(a6989586621679271335 :: m a) >>=@#@$$$ (a6989586621679271336 :: a ~> m b) = a6989586621679271335 >>= a6989586621679271336 

data (>>@#@$) (a1 :: TyFun (m a) (m b ~> m b)) infixl 1 Source #

Instances

Instances details
SMonad m => SingI ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) #

SuppressUnusedWarnings ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679271340 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679271340 :: m a) = (>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type

data (a6989586621679271340 :: m a) >>@#@$$ (b1 :: TyFun (m b) (m b)) infixl 1 Source #

Instances

Instances details
SMonad m => SingI1 ((>>@#@$$) :: m a -> TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: m a). Sing x -> Sing ((>>@#@$$) x :: TyFun (m b) (m b) -> Type) #

(SMonad m, SingI d) => SingI ((>>@#@$$) d :: TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((>>@#@$$) d :: TyFun (m b) (m b) -> Type) #

SuppressUnusedWarnings ((>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type) (a6989586621679271341 :: m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$$) a6989586621679271340 :: TyFun (m b) (m b) -> Type) (a6989586621679271341 :: m b) = a6989586621679271340 >> a6989586621679271341

type family (a6989586621679271340 :: m a) >>@#@$$$ (a6989586621679271341 :: m b) :: m b where ... infixl 1 Source #

Equations

(a6989586621679271340 :: m a) >>@#@$$$ (a6989586621679271341 :: m b) = a6989586621679271340 >> a6989586621679271341 

data ReturnSym0 (a1 :: TyFun a (m a)) Source #

Instances

Instances details
SMonad m => SingI (ReturnSym0 :: TyFun a (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing (ReturnSym0 :: TyFun a (m a) -> Type) #

SuppressUnusedWarnings (ReturnSym0 :: TyFun a (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ReturnSym0 :: TyFun a (m a) -> Type) (a6989586621679271344 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ReturnSym0 :: TyFun a (m a) -> Type) (a6989586621679271344 :: a) = Return a6989586621679271344 :: m a

type family ReturnSym1 (a6989586621679271344 :: a) :: m a where ... Source #

Equations

ReturnSym1 (a6989586621679271344 :: a) = Return a6989586621679271344 :: m a 

data FailSym0 (a1 :: TyFun [Char] (m a)) Source #

Instances

Instances details
SMonadFail m => SingI (FailSym0 :: TyFun [Char] (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sing :: Sing (FailSym0 :: TyFun [Char] (m a) -> Type) #

SuppressUnusedWarnings (FailSym0 :: TyFun [Char] (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679365940 :: [Char]) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679365940 :: [Char]) = Fail a6989586621679365940 :: m a

type family FailSym1 (a6989586621679365940 :: [Char]) :: m a where ... Source #

Equations

FailSym1 a6989586621679365940 = Fail a6989586621679365940 :: m a 

data MapM_Sym0 (a1 :: TyFun (a ~> m b) (t a ~> m ())) Source #

Instances

Instances details
(SFoldable t, SMonad m) => SingI (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) #

SuppressUnusedWarnings (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621679922449 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621679922449 :: a ~> m b) = MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type

data MapM_Sym1 (a6989586621679922449 :: a ~> m b) (b1 :: TyFun (t a) (m ())) Source #

Instances

Instances details
(SFoldable t, SMonad m) => SingI1 (MapM_Sym1 :: (a ~> m b) -> TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing (MapM_Sym1 x :: TyFun (t a) (m ()) -> Type) #

(SFoldable t, SMonad m, SingI d) => SingI (MapM_Sym1 d :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MapM_Sym1 d :: TyFun (t a) (m ()) -> Type) #

SuppressUnusedWarnings (MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type) (a6989586621679922450 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym1 a6989586621679922449 :: TyFun (t a) (m ()) -> Type) (a6989586621679922450 :: t a) = MapM_ a6989586621679922449 a6989586621679922450

type family MapM_Sym2 (a6989586621679922449 :: a ~> m b) (a6989586621679922450 :: t a) :: m () where ... Source #

Equations

MapM_Sym2 (a6989586621679922449 :: a ~> m b) (a6989586621679922450 :: t a) = MapM_ a6989586621679922449 a6989586621679922450 

data Sequence_Sym0 (a1 :: TyFun (t (m a)) (m ())) Source #

Instances

Instances details
(SFoldable t, SMonad m) => SingI (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) #

SuppressUnusedWarnings (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621679922425 :: t (m a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621679922425 :: t (m a)) = Sequence_ a6989586621679922425

type family Sequence_Sym1 (a6989586621679922425 :: t (m a)) :: m () where ... Source #

Equations

Sequence_Sym1 (a6989586621679922425 :: t (m a)) = Sequence_ a6989586621679922425 

data (=<<@#@$) (a1 :: TyFun (a ~> m b) (m a ~> m b)) infixr 1 Source #

Instances

Instances details
SMonad m => SingI ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) #

SuppressUnusedWarnings ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679271176 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679271176 :: a ~> m b) = (=<<@#@$$) a6989586621679271176

data (a6989586621679271176 :: a ~> m b) =<<@#@$$ (b1 :: TyFun (m a) (m b)) infixr 1 Source #

Instances

Instances details
SMonad m => SingI1 ((=<<@#@$$) :: (a ~> m b) -> TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing ((=<<@#@$$) x) #

(SMonad m, SingI d) => SingI ((=<<@#@$$) d :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sing :: Sing ((=<<@#@$$) d) #

SuppressUnusedWarnings ((=<<@#@$$) a6989586621679271176 :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$$) a6989586621679271176 :: TyFun (m a) (m b) -> Type) (a6989586621679271177 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$$) a6989586621679271176 :: TyFun (m a) (m b) -> Type) (a6989586621679271177 :: m a) = a6989586621679271176 =<< a6989586621679271177

type family (a6989586621679271176 :: a ~> m b) =<<@#@$$$ (a6989586621679271177 :: m a) :: m b where ... infixr 1 Source #

Equations

(a6989586621679271176 :: a ~> m b) =<<@#@$$$ (a6989586621679271177 :: m a) = a6989586621679271176 =<< a6989586621679271177 

Folds and traversals

data ElemSym0 (a1 :: TyFun a (t a ~> Bool)) Source #

Instances

Instances details
(SFoldable t, SEq a) => SingI (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) #

SuppressUnusedWarnings (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922567 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922567 :: a) = ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type

data ElemSym1 (a6989586621679922567 :: a) (b :: TyFun (t a) Bool) Source #

Instances

Instances details
(SFoldable t, SEq a) => SingI1 (ElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ElemSym1 x :: TyFun (t a) Bool -> Type) #

(SFoldable t, SEq a, SingI d) => SingI (ElemSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ElemSym1 d :: TyFun (t a) Bool -> Type) #

SuppressUnusedWarnings (ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type) (a6989586621679922568 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621679922567 :: TyFun (t a) Bool -> Type) (a6989586621679922568 :: t a) = Elem a6989586621679922567 a6989586621679922568

type family ElemSym2 (a6989586621679922567 :: a) (a6989586621679922568 :: t a) :: Bool where ... Source #

Equations

ElemSym2 (a6989586621679922567 :: a) (a6989586621679922568 :: t a) = Elem a6989586621679922567 a6989586621679922568 

data FoldMapSym0 (a1 :: TyFun (a ~> m) (t a ~> m)) Source #

Instances

Instances details
(SFoldable t, SMonoid m) => SingI (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) #

SuppressUnusedWarnings (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621679922515 :: a ~> m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621679922515 :: a ~> m) = FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type

data FoldMapSym1 (a6989586621679922515 :: a ~> m) (b :: TyFun (t a) m) Source #

Instances

Instances details
(SFoldable t, SMonoid m) => SingI1 (FoldMapSym1 :: (a ~> m) -> TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> m). Sing x -> Sing (FoldMapSym1 x :: TyFun (t a) m -> Type) #

(SFoldable t, SMonoid m, SingI d) => SingI (FoldMapSym1 d :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldMapSym1 d :: TyFun (t a) m -> Type) #

SuppressUnusedWarnings (FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type) (a6989586621679922516 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym1 a6989586621679922515 :: TyFun (t a) m -> Type) (a6989586621679922516 :: t a) = FoldMap a6989586621679922515 a6989586621679922516

type family FoldMapSym2 (a6989586621679922515 :: a ~> m) (a6989586621679922516 :: t a) :: m where ... Source #

Equations

FoldMapSym2 (a6989586621679922515 :: a ~> m) (a6989586621679922516 :: t a) = FoldMap a6989586621679922515 a6989586621679922516 

data FoldrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b))) Source #

Instances

Instances details
SFoldable t => SingI (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) #

SuppressUnusedWarnings (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922521 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922521 :: a ~> (b ~> b)) = FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type

data FoldrSym1 (a6989586621679922521 :: a ~> (b ~> b)) (b1 :: TyFun b (t a ~> b)) Source #

Instances

Instances details
SFoldable t => SingI1 (FoldrSym1 :: (a ~> (b ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (FoldrSym1 x :: TyFun b (t a ~> b) -> Type) #

(SFoldable t, SingI d) => SingI (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym1 d :: TyFun b (t a ~> b) -> Type) #

SuppressUnusedWarnings (FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type) (a6989586621679922522 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621679922521 :: TyFun b (t a ~> b) -> Type) (a6989586621679922522 :: b) = FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type

data FoldrSym2 (a6989586621679922521 :: a ~> (b ~> b)) (a6989586621679922522 :: b) (c :: TyFun (t a) b) Source #

Instances

Instances details
(SFoldable t, SingI d) => SingI1 (FoldrSym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldrSym2 d x :: TyFun (t a) b -> Type) #

SFoldable t => SingI2 (FoldrSym2 :: (a ~> (b ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (FoldrSym2 x y :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldrSym2 d1 d2 :: TyFun (t a) b -> Type) #

SuppressUnusedWarnings (FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type) (a6989586621679922523 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym2 a6989586621679922521 a6989586621679922522 :: TyFun (t a) b -> Type) (a6989586621679922523 :: t a) = Foldr a6989586621679922521 a6989586621679922522 a6989586621679922523

type family FoldrSym3 (a6989586621679922521 :: a ~> (b ~> b)) (a6989586621679922522 :: b) (a6989586621679922523 :: t a) :: b where ... Source #

Equations

FoldrSym3 (a6989586621679922521 :: a ~> (b ~> b)) (a6989586621679922522 :: b) (a6989586621679922523 :: t a) = Foldr a6989586621679922521 a6989586621679922522 a6989586621679922523 

data FoldlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b))) Source #

Instances

Instances details
SFoldable t => SingI (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) #

SuppressUnusedWarnings (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922535 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621679922535 :: b ~> (a ~> b)) = FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type

data FoldlSym1 (a6989586621679922535 :: b ~> (a ~> b)) (b1 :: TyFun b (t a ~> b)) Source #

Instances

Instances details
SFoldable t => SingI1 (FoldlSym1 :: (b ~> (a ~> b)) -> TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (FoldlSym1 x :: TyFun b (t a ~> b) -> Type) #

(SFoldable t, SingI d) => SingI (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym1 d :: TyFun b (t a ~> b) -> Type) #

SuppressUnusedWarnings (FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type) (a6989586621679922536 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621679922535 :: TyFun b (t a ~> b) -> Type) (a6989586621679922536 :: b) = FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type

data FoldlSym2 (a6989586621679922535 :: b ~> (a ~> b)) (a6989586621679922536 :: b) (c :: TyFun (t a) b) Source #

Instances

Instances details
(SFoldable t, SingI d) => SingI1 (FoldlSym2 d :: b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FoldlSym2 d x :: TyFun (t a) b -> Type) #

SFoldable t => SingI2 (FoldlSym2 :: (b ~> (a ~> b)) -> b -> TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (FoldlSym2 x y :: TyFun (t a) b -> Type) #

(SFoldable t, SingI d1, SingI d2) => SingI (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (FoldlSym2 d1 d2 :: TyFun (t a) b -> Type) #

SuppressUnusedWarnings (FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type) (a6989586621679922537 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym2 a6989586621679922535 a6989586621679922536 :: TyFun (t a) b -> Type) (a6989586621679922537 :: t a) = Foldl a6989586621679922535 a6989586621679922536 a6989586621679922537

type family FoldlSym3 (a6989586621679922535 :: b ~> (a ~> b)) (a6989586621679922536 :: b) (a6989586621679922537 :: t a) :: b where ... Source #

Equations

FoldlSym3 (a6989586621679922535 :: b ~> (a ~> b)) (a6989586621679922536 :: b) (a6989586621679922537 :: t a) = Foldl a6989586621679922535 a6989586621679922536 a6989586621679922537 

data Foldr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (t a ~> a)) Source #

Instances

Instances details
SFoldable t => SingI (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) #

SuppressUnusedWarnings (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922548 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922548 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type

data Foldr1Sym1 (a6989586621679922548 :: a ~> (a ~> a)) (b :: TyFun (t a) a) Source #

Instances

Instances details
SFoldable t => SingI1 (Foldr1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Foldr1Sym1 x :: TyFun (t a) a -> Type) #

(SFoldable t, SingI d) => SingI (Foldr1Sym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldr1Sym1 d :: TyFun (t a) a -> Type) #

SuppressUnusedWarnings (Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type) (a6989586621679922549 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym1 a6989586621679922548 :: TyFun (t a) a -> Type) (a6989586621679922549 :: t a) = Foldr1 a6989586621679922548 a6989586621679922549

type family Foldr1Sym2 (a6989586621679922548 :: a ~> (a ~> a)) (a6989586621679922549 :: t a) :: a where ... Source #

Equations

Foldr1Sym2 (a6989586621679922548 :: a ~> (a ~> a)) (a6989586621679922549 :: t a) = Foldr1 a6989586621679922548 a6989586621679922549 

data Foldl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) (t a ~> a)) Source #

Instances

Instances details
SFoldable t => SingI (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) #

SuppressUnusedWarnings (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922553 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621679922553 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type

data Foldl1Sym1 (a6989586621679922553 :: a ~> (a ~> a)) (b :: TyFun (t a) a) Source #

Instances

Instances details
SFoldable t => SingI1 (Foldl1Sym1 :: (a ~> (a ~> a)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Foldl1Sym1 x :: TyFun (t a) a -> Type) #

(SFoldable t, SingI d) => SingI (Foldl1Sym1 d :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (Foldl1Sym1 d :: TyFun (t a) a -> Type) #

SuppressUnusedWarnings (Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type) (a6989586621679922554 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym1 a6989586621679922553 :: TyFun (t a) a -> Type) (a6989586621679922554 :: t a) = Foldl1 a6989586621679922553 a6989586621679922554

type family Foldl1Sym2 (a6989586621679922553 :: a ~> (a ~> a)) (a6989586621679922554 :: t a) :: a where ... Source #

Equations

Foldl1Sym2 (a6989586621679922553 :: a ~> (a ~> a)) (a6989586621679922554 :: t a) = Foldl1 a6989586621679922553 a6989586621679922554 

data MaximumSym0 (a1 :: TyFun (t a) a) Source #

Instances

Instances details
(SFoldable t, SOrd a) => SingI (MaximumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MaximumSym0 :: TyFun (t a) a -> Type) #

SuppressUnusedWarnings (MaximumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621679922571 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621679922571 :: t a) = Maximum a6989586621679922571

type family MaximumSym1 (a6989586621679922571 :: t a) :: a where ... Source #

Equations

MaximumSym1 (a6989586621679922571 :: t a) = Maximum a6989586621679922571 

data MinimumSym0 (a1 :: TyFun (t a) a) Source #

Instances

Instances details
(SFoldable t, SOrd a) => SingI (MinimumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (MinimumSym0 :: TyFun (t a) a -> Type) #

SuppressUnusedWarnings (MinimumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621679922574 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621679922574 :: t a) = Minimum a6989586621679922574

type family MinimumSym1 (a6989586621679922574 :: t a) :: a where ... Source #

Equations

MinimumSym1 (a6989586621679922574 :: t a) = Minimum a6989586621679922574 

data ProductSym0 (a1 :: TyFun (t a) a) Source #

Instances

Instances details
(SFoldable t, SNum a) => SingI (ProductSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ProductSym0 :: TyFun (t a) a -> Type) #

SuppressUnusedWarnings (ProductSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621679922580 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621679922580 :: t a) = Product a6989586621679922580

type family ProductSym1 (a6989586621679922580 :: t a) :: a where ... Source #

Equations

ProductSym1 (a6989586621679922580 :: t a) = Product a6989586621679922580 

data SumSym0 (a1 :: TyFun (t a) a) Source #

Instances

Instances details
(SFoldable t, SNum a) => SingI (SumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (SumSym0 :: TyFun (t a) a -> Type) #

SuppressUnusedWarnings (SumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621679922577 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621679922577 :: t a) = Sum a6989586621679922577

type family SumSym1 (a6989586621679922577 :: t a) :: a where ... Source #

Equations

SumSym1 (a6989586621679922577 :: t a) = Sum a6989586621679922577 

data TraverseSym0 (a1 :: TyFun (a ~> f b) (t a ~> f (t b))) Source #

Instances

Instances details
(STraversable t, SApplicative f) => SingI (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) #

SuppressUnusedWarnings (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680096860 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680096860 :: a ~> f b) = TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type

data TraverseSym1 (a6989586621680096860 :: a ~> f b) (b1 :: TyFun (t a) (f (t b))) Source #

Instances

Instances details
(STraversable t, SApplicative f) => SingI1 (TraverseSym1 :: (a ~> f b) -> TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> f b). Sing x -> Sing (TraverseSym1 x :: TyFun (t a) (f (t b)) -> Type) #

(STraversable t, SApplicative f, SingI d) => SingI (TraverseSym1 d :: TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (TraverseSym1 d :: TyFun (t a) (f (t b)) -> Type) #

SuppressUnusedWarnings (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680096861 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym1 a6989586621680096860 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680096861 :: t a) = Traverse a6989586621680096860 a6989586621680096861

type family TraverseSym2 (a6989586621680096860 :: a ~> f b) (a6989586621680096861 :: t a) :: f (t b) where ... Source #

Equations

TraverseSym2 (a6989586621680096860 :: a ~> f b) (a6989586621680096861 :: t a) = Traverse a6989586621680096860 a6989586621680096861 

data SequenceASym0 (a1 :: TyFun (t (f a)) (f (t a))) Source #

Instances

Instances details
(STraversable t, SApplicative f) => SingI (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) #

SuppressUnusedWarnings (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680096864 :: t (f a)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680096864 :: t (f a)) = SequenceA a6989586621680096864

type family SequenceASym1 (a6989586621680096864 :: t (f a)) :: f (t a) where ... Source #

Equations

SequenceASym1 (a6989586621680096864 :: t (f a)) = SequenceA a6989586621680096864 

data MapMSym0 (a1 :: TyFun (a ~> m b) (t a ~> m (t b))) Source #

Instances

Instances details
(STraversable t, SMonad m) => SingI (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) #

SuppressUnusedWarnings (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680096868 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680096868 :: a ~> m b) = MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type

data MapMSym1 (a6989586621680096868 :: a ~> m b) (b1 :: TyFun (t a) (m (t b))) Source #

Instances

Instances details
(STraversable t, SMonad m) => SingI1 (MapMSym1 :: (a ~> m b) -> TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

liftSing :: forall (x :: a ~> m b). Sing x -> Sing (MapMSym1 x :: TyFun (t a) (m (t b)) -> Type) #

(STraversable t, SMonad m, SingI d) => SingI (MapMSym1 d :: TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (MapMSym1 d :: TyFun (t a) (m (t b)) -> Type) #

SuppressUnusedWarnings (MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680096869 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym1 a6989586621680096868 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680096869 :: t a) = MapM a6989586621680096868 a6989586621680096869

type family MapMSym2 (a6989586621680096868 :: a ~> m b) (a6989586621680096869 :: t a) :: m (t b) where ... Source #

Equations

MapMSym2 (a6989586621680096868 :: a ~> m b) (a6989586621680096869 :: t a) = MapM a6989586621680096868 a6989586621680096869 

data SequenceSym0 (a1 :: TyFun (t (m a)) (m (t a))) Source #

Instances

Instances details
(STraversable t, SMonad m) => SingI (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

Methods

sing :: Sing (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) #

SuppressUnusedWarnings (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680096872 :: t (m a)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680096872 :: t (m a)) = Sequence a6989586621680096872

type family SequenceSym1 (a6989586621680096872 :: t (m a)) :: m (t a) where ... Source #

Equations

SequenceSym1 (a6989586621680096872 :: t (m a)) = Sequence a6989586621680096872 

Miscellaneous functions

data IdSym0 (a1 :: TyFun a a) Source #

Instances

Instances details
SingI (IdSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (IdSym0 :: TyFun a a -> Type) #

SuppressUnusedWarnings (IdSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (IdSym0 :: TyFun a a -> Type) (a6989586621679154359 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (IdSym0 :: TyFun a a -> Type) (a6989586621679154359 :: a) = Id a6989586621679154359

type family IdSym1 (a6989586621679154359 :: a) :: a where ... Source #

Equations

IdSym1 (a6989586621679154359 :: a) = Id a6989586621679154359 

data ConstSym0 (a1 :: TyFun a (b ~> a)) Source #

Instances

Instances details
SingI (ConstSym0 :: TyFun a (b ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (ConstSym0 :: TyFun a (b ~> a) -> Type) #

SuppressUnusedWarnings (ConstSym0 :: TyFun a (b ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679154354 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679154354 :: a) = ConstSym1 a6989586621679154354 :: TyFun b a -> Type

data ConstSym1 (a6989586621679154354 :: a) (b1 :: TyFun b a) Source #

Instances

Instances details
SingI1 (ConstSym1 :: a -> TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ConstSym1 x :: TyFun b a -> Type) #

SingI d => SingI (ConstSym1 d :: TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (ConstSym1 d :: TyFun b a -> Type) #

SuppressUnusedWarnings (ConstSym1 a6989586621679154354 :: TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym1 a6989586621679154354 :: TyFun b a -> Type) (a6989586621679154355 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym1 a6989586621679154354 :: TyFun b a -> Type) (a6989586621679154355 :: b) = Const a6989586621679154354 a6989586621679154355

type family ConstSym2 (a6989586621679154354 :: a) (a6989586621679154355 :: b) :: a where ... Source #

Equations

ConstSym2 (a6989586621679154354 :: a) (a6989586621679154355 :: b) = Const a6989586621679154354 a6989586621679154355 

data (.@#@$) (a1 :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c))) infixr 9 Source #

Instances

Instances details
SingI ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) #

SuppressUnusedWarnings ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679154339 :: b ~> c) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679154339 :: b ~> c) = (.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type

data (a6989586621679154339 :: b ~> c) .@#@$$ (b1 :: TyFun (a ~> b) (a ~> c)) infixr 9 Source #

Instances

Instances details
SingI1 ((.@#@$$) :: (b ~> c) -> TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: b ~> c). Sing x -> Sing ((.@#@$$) x :: TyFun (a ~> b) (a ~> c) -> Type) #

SingI d => SingI ((.@#@$$) d :: TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((.@#@$$) d :: TyFun (a ~> b) (a ~> c) -> Type) #

SuppressUnusedWarnings ((.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679154340 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679154339 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679154340 :: a ~> b) = a6989586621679154339 .@#@$$$ a6989586621679154340

data ((a6989586621679154339 :: b ~> c) .@#@$$$ (a6989586621679154340 :: a ~> b)) (c1 :: TyFun a c) infixr 9 Source #

Instances

Instances details
SingI2 ((.@#@$$$) :: (b ~> c) -> (a ~> b) -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: b ~> c) (y :: a ~> b). Sing x -> Sing y -> Sing (x .@#@$$$ y) #

SingI d => SingI1 ((.@#@$$$) d :: (a ~> b) -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (d .@#@$$$ x) #

(SingI d1, SingI d2) => SingI (d1 .@#@$$$ d2 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (d1 .@#@$$$ d2) #

SuppressUnusedWarnings (a6989586621679154339 .@#@$$$ a6989586621679154340 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (a6989586621679154339 .@#@$$$ a6989586621679154340 :: TyFun a c -> Type) (a6989586621679154341 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (a6989586621679154339 .@#@$$$ a6989586621679154340 :: TyFun a c -> Type) (a6989586621679154341 :: a) = (a6989586621679154339 . a6989586621679154340) a6989586621679154341

type family ((a6989586621679154339 :: b ~> c) .@#@$$$$ (a6989586621679154340 :: a ~> b)) (a6989586621679154341 :: a) :: c where ... infixr 9 Source #

Equations

((a6989586621679154339 :: b ~> c) .@#@$$$$ (a6989586621679154340 :: a ~> b)) (a6989586621679154341 :: a) = (a6989586621679154339 . a6989586621679154340) a6989586621679154341 

data FlipSym0 (a1 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c))) Source #

Instances

Instances details
SingI (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) #

SuppressUnusedWarnings (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679154327 :: a ~> (b ~> c)) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679154327 :: a ~> (b ~> c)) = FlipSym1 a6989586621679154327

data FlipSym1 (a6989586621679154327 :: a ~> (b ~> c)) (b1 :: TyFun b (a ~> c)) Source #

Instances

Instances details
SingI1 (FlipSym1 :: (a ~> (b ~> c)) -> TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (FlipSym1 x) #

SingI d => SingI (FlipSym1 d :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym1 d) #

SuppressUnusedWarnings (FlipSym1 a6989586621679154327 :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679154327 :: TyFun b (a ~> c) -> Type) (a6989586621679154328 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679154327 :: TyFun b (a ~> c) -> Type) (a6989586621679154328 :: b) = FlipSym2 a6989586621679154327 a6989586621679154328

data FlipSym2 (a6989586621679154327 :: a ~> (b ~> c)) (a6989586621679154328 :: b) (c1 :: TyFun a c) Source #

Instances

Instances details
SingI d => SingI1 (FlipSym2 d :: b -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: b). Sing x -> Sing (FlipSym2 d x) #

SingI2 (FlipSym2 :: (a ~> (b ~> c)) -> b -> TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: b). Sing x -> Sing y -> Sing (FlipSym2 x y) #

(SingI d1, SingI d2) => SingI (FlipSym2 d1 d2 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (FlipSym2 d1 d2) #

SuppressUnusedWarnings (FlipSym2 a6989586621679154327 a6989586621679154328 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym2 a6989586621679154327 a6989586621679154328 :: TyFun a c -> Type) (a6989586621679154329 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym2 a6989586621679154327 a6989586621679154328 :: TyFun a c -> Type) (a6989586621679154329 :: a) = Flip a6989586621679154327 a6989586621679154328 a6989586621679154329

type family FlipSym3 (a6989586621679154327 :: a ~> (b ~> c)) (a6989586621679154328 :: b) (a6989586621679154329 :: a) :: c where ... Source #

Equations

FlipSym3 (a6989586621679154327 :: a ~> (b ~> c)) (a6989586621679154328 :: b) (a6989586621679154329 :: a) = Flip a6989586621679154327 a6989586621679154328 a6989586621679154329 

data ($@#@$) (a1 :: TyFun (a ~> b) (a ~> b)) infixr 0 Source #

Instances

Instances details
SingI (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) #

SuppressUnusedWarnings (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154308 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154308 :: a ~> b) = ($@#@$$) a6989586621679154308

data (a6989586621679154308 :: a ~> b) $@#@$$ (b1 :: TyFun a b) infixr 0 Source #

Instances

Instances details
SingI1 (($@#@$$) :: (a ~> b) -> TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (($@#@$$) x) #

SingI d => SingI (($@#@$$) d :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($@#@$$) d) #

SuppressUnusedWarnings (($@#@$$) a6989586621679154308 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$$) a6989586621679154308 :: TyFun a b -> Type) (a6989586621679154309 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$$) a6989586621679154308 :: TyFun a b -> Type) (a6989586621679154309 :: a) = a6989586621679154308 $ a6989586621679154309

type family (a6989586621679154308 :: a ~> b) $@#@$$$ (a6989586621679154309 :: a) :: b where ... infixr 0 Source #

Equations

(a6989586621679154308 :: a ~> b) $@#@$$$ (a6989586621679154309 :: a) = a6989586621679154308 $ a6989586621679154309 

data UntilSym0 (a1 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a))) Source #

Instances

Instances details
SingI (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) #

SuppressUnusedWarnings (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679154281 :: a ~> Bool) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679154281 :: a ~> Bool) = UntilSym1 a6989586621679154281

data UntilSym1 (a6989586621679154281 :: a ~> Bool) (b :: TyFun (a ~> a) (a ~> a)) Source #

Instances

Instances details
SingI d => SingI (UntilSym1 d :: TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym1 d) #

SuppressUnusedWarnings (UntilSym1 a6989586621679154281 :: TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SingI1 (UntilSym1 :: (a ~> Bool) -> TyFun (a ~> a) (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (UntilSym1 x) #

type Apply (UntilSym1 a6989586621679154281 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679154282 :: a ~> a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym1 a6989586621679154281 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679154282 :: a ~> a) = UntilSym2 a6989586621679154281 a6989586621679154282

data UntilSym2 (a6989586621679154281 :: a ~> Bool) (a6989586621679154282 :: a ~> a) (c :: TyFun a a) Source #

Instances

Instances details
SingI d => SingI1 (UntilSym2 d :: (a ~> a) -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> a). Sing x -> Sing (UntilSym2 d x) #

SingI2 (UntilSym2 :: (a ~> Bool) -> (a ~> a) -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing2 :: forall (x :: a ~> Bool) (y :: a ~> a). Sing x -> Sing y -> Sing (UntilSym2 x y) #

(SingI d1, SingI d2) => SingI (UntilSym2 d1 d2 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (UntilSym2 d1 d2) #

SuppressUnusedWarnings (UntilSym2 a6989586621679154281 a6989586621679154282 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym2 a6989586621679154281 a6989586621679154282 :: TyFun a a -> Type) (a6989586621679154283 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym2 a6989586621679154281 a6989586621679154282 :: TyFun a a -> Type) (a6989586621679154283 :: a) = Until a6989586621679154281 a6989586621679154282 a6989586621679154283

type family UntilSym3 (a6989586621679154281 :: a ~> Bool) (a6989586621679154282 :: a ~> a) (a6989586621679154283 :: a) :: a where ... Source #

Equations

UntilSym3 (a6989586621679154281 :: a ~> Bool) (a6989586621679154282 :: a ~> a) (a6989586621679154283 :: a) = Until a6989586621679154281 a6989586621679154282 a6989586621679154283 

data AsTypeOfSym0 (a1 :: TyFun a (a ~> a)) Source #

Instances

Instances details
SingI (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679154319 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679154319 :: a) = AsTypeOfSym1 a6989586621679154319

data AsTypeOfSym1 (a6989586621679154319 :: a) (b :: TyFun a a) Source #

Instances

Instances details
SingI1 (AsTypeOfSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (AsTypeOfSym1 x) #

SingI d => SingI (AsTypeOfSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (AsTypeOfSym1 d) #

SuppressUnusedWarnings (AsTypeOfSym1 a6989586621679154319 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym1 a6989586621679154319 :: TyFun a a -> Type) (a6989586621679154320 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym1 a6989586621679154319 :: TyFun a a -> Type) (a6989586621679154320 :: a) = AsTypeOf a6989586621679154319 a6989586621679154320

type family AsTypeOfSym2 (a6989586621679154319 :: a) (a6989586621679154320 :: a) :: a where ... Source #

Equations

AsTypeOfSym2 (a6989586621679154319 :: a) (a6989586621679154320 :: a) = AsTypeOf a6989586621679154319 a6989586621679154320 

data ErrorSym0 (a1 :: TyFun Symbol a) Source #

Instances

Instances details
SingI (ErrorSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

sing :: Sing (ErrorSym0 :: TyFun Symbol a -> Type) #

SuppressUnusedWarnings (ErrorSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorSym0 :: TyFun Symbol a -> Type) (a6989586621679368947 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorSym0 :: TyFun Symbol a -> Type) (a6989586621679368947 :: Symbol) = Error a6989586621679368947 :: a

type family ErrorSym1 (a6989586621679368947 :: Symbol) :: a where ... Source #

Equations

ErrorSym1 a6989586621679368947 = Error a6989586621679368947 :: a 

data ErrorWithoutStackTraceSym0 (a1 :: TyFun Symbol a) Source #

Instances

Instances details
SingI (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) (a6989586621679369227 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol a -> Type) (a6989586621679369227 :: Symbol) = ErrorWithoutStackTrace a6989586621679369227 :: a

type family ErrorWithoutStackTraceSym1 (a6989586621679369227 :: Symbol) :: a where ... Source #

Equations

ErrorWithoutStackTraceSym1 a6989586621679369227 = ErrorWithoutStackTrace a6989586621679369227 :: a 

type family UndefinedSym0 :: a where ... Source #

data SeqSym0 (a1 :: TyFun a (b ~> b)) infixr 0 Source #

Instances

Instances details
SingI (SeqSym0 :: TyFun a (b ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (SeqSym0 :: TyFun a (b ~> b) -> Type) #

SuppressUnusedWarnings (SeqSym0 :: TyFun a (b ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) (a6989586621679154272 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) (a6989586621679154272 :: a) = SeqSym1 a6989586621679154272 :: TyFun b b -> Type

data SeqSym1 (a6989586621679154272 :: a) (b1 :: TyFun b b) infixr 0 Source #

Instances

Instances details
SingI1 (SeqSym1 :: a -> TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (SeqSym1 x :: TyFun b b -> Type) #

SingI d => SingI (SeqSym1 d :: TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (SeqSym1 d :: TyFun b b -> Type) #

SuppressUnusedWarnings (SeqSym1 a6989586621679154272 :: TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym1 a6989586621679154272 :: TyFun b b -> Type) (a6989586621679154273 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym1 a6989586621679154272 :: TyFun b b -> Type) (a6989586621679154273 :: b) = Seq a6989586621679154272 a6989586621679154273

type family SeqSym2 (a6989586621679154272 :: a) (a6989586621679154273 :: b) :: b where ... infixr 0 Source #

Equations

SeqSym2 (a6989586621679154272 :: a) (a6989586621679154273 :: b) = Seq a6989586621679154272 a6989586621679154273 

data ($!@#@$) (a1 :: TyFun (a ~> b) (a ~> b)) infixr 0 Source #

Instances

Instances details
SingI (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) #

SuppressUnusedWarnings (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154299 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679154299 :: a ~> b) = ($!@#@$$) a6989586621679154299

data (a6989586621679154299 :: a ~> b) $!@#@$$ (b1 :: TyFun a b) infixr 0 Source #

Instances

Instances details
SingI1 (($!@#@$$) :: (a ~> b) -> TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (($!@#@$$) x) #

SingI d => SingI (($!@#@$$) d :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (($!@#@$$) d) #

SuppressUnusedWarnings (($!@#@$$) a6989586621679154299 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$$) a6989586621679154299 :: TyFun a b -> Type) (a6989586621679154300 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$$) a6989586621679154299 :: TyFun a b -> Type) (a6989586621679154300 :: a) = a6989586621679154299 $! a6989586621679154300

type family (a6989586621679154299 :: a ~> b) $!@#@$$$ (a6989586621679154300 :: a) :: b where ... infixr 0 Source #

Equations

(a6989586621679154299 :: a ~> b) $!@#@$$$ (a6989586621679154300 :: a) = a6989586621679154299 $! a6989586621679154300 

List operations

data MapSym0 (a1 :: TyFun (a ~> b) ([a] ~> [b])) Source #

Instances

Instances details
SingI (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) #

SuppressUnusedWarnings (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679154373 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679154373 :: a ~> b) = MapSym1 a6989586621679154373

data MapSym1 (a6989586621679154373 :: a ~> b) (b1 :: TyFun [a] [b]) Source #

Instances

Instances details
SingI1 (MapSym1 :: (a ~> b) -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: a ~> b). Sing x -> Sing (MapSym1 x) #

SingI d => SingI (MapSym1 d :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing (MapSym1 d) #

SuppressUnusedWarnings (MapSym1 a6989586621679154373 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym1 a6989586621679154373 :: TyFun [a] [b] -> Type) (a6989586621679154374 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym1 a6989586621679154373 :: TyFun [a] [b] -> Type) (a6989586621679154374 :: [a]) = Map a6989586621679154373 a6989586621679154374

type family MapSym2 (a6989586621679154373 :: a ~> b) (a6989586621679154374 :: [a]) :: [b] where ... Source #

Equations

MapSym2 (a6989586621679154373 :: a ~> b) (a6989586621679154374 :: [a]) = Map a6989586621679154373 a6989586621679154374 

data (++@#@$) (a1 :: TyFun [a] ([a] ~> [a])) infixr 5 Source #

Instances

Instances details
SingI ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679154364 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679154364 :: [a]) = (++@#@$$) a6989586621679154364

data (a6989586621679154364 :: [a]) ++@#@$$ (b :: TyFun [a] [a]) infixr 5 Source #

Instances

Instances details
SingI1 ((++@#@$$) :: [a] -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing ((++@#@$$) x) #

SingI d => SingI ((++@#@$$) d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

Methods

sing :: Sing ((++@#@$$) d) #

SuppressUnusedWarnings ((++@#@$$) a6989586621679154364 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$$) a6989586621679154364 :: TyFun [a] [a] -> Type) (a6989586621679154365 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$$) a6989586621679154364 :: TyFun [a] [a] -> Type) (a6989586621679154365 :: [a]) = a6989586621679154364 ++ a6989586621679154365

type family (a6989586621679154364 :: [a]) ++@#@$$$ (a6989586621679154365 :: [a]) :: [a] where ... infixr 5 Source #

Equations

(a6989586621679154364 :: [a]) ++@#@$$$ (a6989586621679154365 :: [a]) = a6989586621679154364 ++ a6989586621679154365 

data FilterSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a])) Source #

Instances

Instances details
SingI (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544674 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544674 :: a ~> Bool) = FilterSym1 a6989586621679544674

data FilterSym1 (a6989586621679544674 :: a ~> Bool) (b :: TyFun [a] [a]) Source #

Instances

Instances details
SingI d => SingI (FilterSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (FilterSym1 d) #

SuppressUnusedWarnings (FilterSym1 a6989586621679544674 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI1 (FilterSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (FilterSym1 x) #

type Apply (FilterSym1 a6989586621679544674 :: TyFun [a] [a] -> Type) (a6989586621679544675 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym1 a6989586621679544674 :: TyFun [a] [a] -> Type) (a6989586621679544675 :: [a]) = Filter a6989586621679544674 a6989586621679544675

type family FilterSym2 (a6989586621679544674 :: a ~> Bool) (a6989586621679544675 :: [a]) :: [a] where ... Source #

Equations

FilterSym2 (a6989586621679544674 :: a ~> Bool) (a6989586621679544675 :: [a]) = Filter a6989586621679544674 a6989586621679544675 

data HeadSym0 (a1 :: TyFun [a] a) Source #

Instances

Instances details
SingI (HeadSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (HeadSym0 :: TyFun [a] a -> Type) #

SuppressUnusedWarnings (HeadSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679545466 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679545466 :: [a]) = Head a6989586621679545466

type family HeadSym1 (a6989586621679545466 :: [a]) :: a where ... Source #

Equations

HeadSym1 (a6989586621679545466 :: [a]) = Head a6989586621679545466 

data LastSym0 (a1 :: TyFun [a] a) Source #

Instances

Instances details
SingI (LastSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LastSym0 :: TyFun [a] a -> Type) #

SuppressUnusedWarnings (LastSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679545460 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679545460 :: [a]) = Last a6989586621679545460

type family LastSym1 (a6989586621679545460 :: [a]) :: a where ... Source #

Equations

LastSym1 (a6989586621679545460 :: [a]) = Last a6989586621679545460 

data TailSym0 (a1 :: TyFun [a] [a]) Source #

Instances

Instances details
SingI (TailSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TailSym0 :: TyFun [a] [a] -> Type) #

SuppressUnusedWarnings (TailSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679545456 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679545456 :: [a]) = Tail a6989586621679545456

type family TailSym1 (a6989586621679545456 :: [a]) :: [a] where ... Source #

Equations

TailSym1 (a6989586621679545456 :: [a]) = Tail a6989586621679545456 

data InitSym0 (a1 :: TyFun [a] [a]) Source #

Instances

Instances details
SingI (InitSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (InitSym0 :: TyFun [a] [a] -> Type) #

SuppressUnusedWarnings (InitSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679545444 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679545444 :: [a]) = Init a6989586621679545444

type family InitSym1 (a6989586621679545444 :: [a]) :: [a] where ... Source #

Equations

InitSym1 (a6989586621679545444 :: [a]) = Init a6989586621679545444 

data (!!@#@$) (a1 :: TyFun [a] (Natural ~> a)) infixl 9 Source #

Instances

Instances details
SingI ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) #

SuppressUnusedWarnings ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679544266 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679544266 :: [a]) = (!!@#@$$) a6989586621679544266

data (a6989586621679544266 :: [a]) !!@#@$$ (b :: TyFun Natural a) infixl 9 Source #

Instances

Instances details
SingI1 ((!!@#@$$) :: [a] -> TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing ((!!@#@$$) x) #

SingI d => SingI ((!!@#@$$) d :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing ((!!@#@$$) d) #

SuppressUnusedWarnings ((!!@#@$$) a6989586621679544266 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$$) a6989586621679544266 :: TyFun Natural a -> Type) (a6989586621679544267 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$$) a6989586621679544266 :: TyFun Natural a -> Type) (a6989586621679544267 :: Natural) = a6989586621679544266 !! a6989586621679544267

type family (a6989586621679544266 :: [a]) !!@#@$$$ (a6989586621679544267 :: Natural) :: a where ... infixl 9 Source #

Equations

(a6989586621679544266 :: [a]) !!@#@$$$ a6989586621679544267 = a6989586621679544266 !! a6989586621679544267 

data NullSym0 (a1 :: TyFun (t a) Bool) Source #

Instances

Instances details
SFoldable t => SingI (NullSym0 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NullSym0 :: TyFun (t a) Bool -> Type) #

SuppressUnusedWarnings (NullSym0 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621679922560 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621679922560 :: t a) = Null a6989586621679922560

type family NullSym1 (a6989586621679922560 :: t a) :: Bool where ... Source #

Equations

NullSym1 (a6989586621679922560 :: t a) = Null a6989586621679922560 

data LengthSym0 (a1 :: TyFun (t a) Natural) Source #

Instances

Instances details
SFoldable t => SingI (LengthSym0 :: TyFun (t a) Natural -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (LengthSym0 :: TyFun (t a) Natural -> Type) #

SuppressUnusedWarnings (LengthSym0 :: TyFun (t a) Natural -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621679922563 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621679922563 :: t a) = Length a6989586621679922563

type family LengthSym1 (a6989586621679922563 :: t a) :: Natural where ... Source #

Equations

LengthSym1 (a6989586621679922563 :: t a) = Length a6989586621679922563 

data ReverseSym0 (a1 :: TyFun [a] [a]) Source #

Instances

Instances details
SingI (ReverseSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReverseSym0 :: TyFun [a] [a] -> Type) #

SuppressUnusedWarnings (ReverseSym0 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679545429 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679545429 :: [a]) = Reverse a6989586621679545429

type family ReverseSym1 (a6989586621679545429 :: [a]) :: [a] where ... Source #

Equations

ReverseSym1 (a6989586621679545429 :: [a]) = Reverse a6989586621679545429 

Special folds

data AndSym0 (a :: TyFun (t Bool) Bool) Source #

Instances

Instances details
SFoldable t => SingI (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AndSym0 :: TyFun (t Bool) Bool -> Type) #

SuppressUnusedWarnings (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621679922378 :: t Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621679922378 :: t Bool) = And a6989586621679922378

type family AndSym1 (a6989586621679922378 :: t Bool) :: Bool where ... Source #

Equations

AndSym1 (a6989586621679922378 :: t Bool) = And a6989586621679922378 

data OrSym0 (a :: TyFun (t Bool) Bool) Source #

Instances

Instances details
SFoldable t => SingI (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (OrSym0 :: TyFun (t Bool) Bool -> Type) #

SuppressUnusedWarnings (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621679922372 :: t Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621679922372 :: t Bool) = Or a6989586621679922372

type family OrSym1 (a6989586621679922372 :: t Bool) :: Bool where ... Source #

Equations

OrSym1 (a6989586621679922372 :: t Bool) = Or a6989586621679922372 

data AnySym0 (a1 :: TyFun (a ~> Bool) (t a ~> Bool)) Source #

Instances

Instances details
SFoldable t => SingI (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) #

SuppressUnusedWarnings (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922364 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922364 :: a ~> Bool) = AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type

data AnySym1 (a6989586621679922364 :: a ~> Bool) (b :: TyFun (t a) Bool) Source #

Instances

Instances details
SFoldable t => SingI1 (AnySym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (AnySym1 x :: TyFun (t a) Bool -> Type) #

(SFoldable t, SingI d) => SingI (AnySym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AnySym1 d :: TyFun (t a) Bool -> Type) #

SuppressUnusedWarnings (AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type) (a6989586621679922365 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621679922364 :: TyFun (t a) Bool -> Type) (a6989586621679922365 :: t a) = Any a6989586621679922364 a6989586621679922365

type family AnySym2 (a6989586621679922364 :: a ~> Bool) (a6989586621679922365 :: t a) :: Bool where ... Source #

Equations

AnySym2 (a6989586621679922364 :: a ~> Bool) (a6989586621679922365 :: t a) = Any a6989586621679922364 a6989586621679922365 

data AllSym0 (a1 :: TyFun (a ~> Bool) (t a ~> Bool)) Source #

Instances

Instances details
SFoldable t => SingI (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) #

SuppressUnusedWarnings (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922355 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621679922355 :: a ~> Bool) = AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type

data AllSym1 (a6989586621679922355 :: a ~> Bool) (b :: TyFun (t a) Bool) Source #

Instances

Instances details
SFoldable t => SingI1 (AllSym1 :: (a ~> Bool) -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (AllSym1 x :: TyFun (t a) Bool -> Type) #

(SFoldable t, SingI d) => SingI (AllSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (AllSym1 d :: TyFun (t a) Bool -> Type) #

SuppressUnusedWarnings (AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type) (a6989586621679922356 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621679922355 :: TyFun (t a) Bool -> Type) (a6989586621679922356 :: t a) = All a6989586621679922355 a6989586621679922356

type family AllSym2 (a6989586621679922355 :: a ~> Bool) (a6989586621679922356 :: t a) :: Bool where ... Source #

Equations

AllSym2 (a6989586621679922355 :: a ~> Bool) (a6989586621679922356 :: t a) = All a6989586621679922355 a6989586621679922356 

data ConcatSym0 (a1 :: TyFun (t [a]) [a]) Source #

Instances

Instances details
SFoldable t => SingI (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatSym0 :: TyFun (t [a]) [a] -> Type) #

SuppressUnusedWarnings (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621679922398 :: t [a]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621679922398 :: t [a]) = Concat a6989586621679922398

type family ConcatSym1 (a6989586621679922398 :: t [a]) :: [a] where ... Source #

Equations

ConcatSym1 (a6989586621679922398 :: t [a]) = Concat a6989586621679922398 

data ConcatMapSym0 (a1 :: TyFun (a ~> [b]) (t a ~> [b])) Source #

Instances

Instances details
SFoldable t => SingI (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) #

SuppressUnusedWarnings (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621679922383 :: a ~> [b]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621679922383 :: a ~> [b]) = ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type

data ConcatMapSym1 (a6989586621679922383 :: a ~> [b]) (b1 :: TyFun (t a) [b]) Source #

Instances

Instances details
SFoldable t => SingI1 (ConcatMapSym1 :: (a ~> [b]) -> TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a ~> [b]). Sing x -> Sing (ConcatMapSym1 x :: TyFun (t a) [b] -> Type) #

(SFoldable t, SingI d) => SingI (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (ConcatMapSym1 d :: TyFun (t a) [b] -> Type) #

SuppressUnusedWarnings (ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type) (a6989586621679922384 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym1 a6989586621679922383 :: TyFun (t a) [b] -> Type) (a6989586621679922384 :: t a) = ConcatMap a6989586621679922383 a6989586621679922384

type family ConcatMapSym2 (a6989586621679922383 :: a ~> [b]) (a6989586621679922384 :: t a) :: [b] where ... Source #

Equations

ConcatMapSym2 (a6989586621679922383 :: a ~> [b]) (a6989586621679922384 :: t a) = ConcatMap a6989586621679922383 a6989586621679922384 

Building lists

Scans

data ScanlSym0 (a1 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b]))) Source #

Instances

Instances details
SingI (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) #

SuppressUnusedWarnings (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545226 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545226 :: b ~> (a ~> b)) = ScanlSym1 a6989586621679545226

data ScanlSym1 (a6989586621679545226 :: b ~> (a ~> b)) (b1 :: TyFun b ([a] ~> [b])) Source #

Instances

Instances details
SingI1 (ScanlSym1 :: (b ~> (a ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b ~> (a ~> b)). Sing x -> Sing (ScanlSym1 x) #

SingI d => SingI (ScanlSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym1 d) #

SuppressUnusedWarnings (ScanlSym1 a6989586621679545226 :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym1 a6989586621679545226 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545227 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym1 a6989586621679545226 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545227 :: b) = ScanlSym2 a6989586621679545226 a6989586621679545227

data ScanlSym2 (a6989586621679545226 :: b ~> (a ~> b)) (a6989586621679545227 :: b) (c :: TyFun [a] [b]) Source #

Instances

Instances details
SingI d => SingI1 (ScanlSym2 d :: b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanlSym2 d x) #

SingI2 (ScanlSym2 :: (b ~> (a ~> b)) -> b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: b ~> (a ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanlSym2 x y) #

(SingI d1, SingI d2) => SingI (ScanlSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanlSym2 d1 d2) #

SuppressUnusedWarnings (ScanlSym2 a6989586621679545226 a6989586621679545227 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym2 a6989586621679545226 a6989586621679545227 :: TyFun [a] [b] -> Type) (a6989586621679545228 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym2 a6989586621679545226 a6989586621679545227 :: TyFun [a] [b] -> Type) (a6989586621679545228 :: [a]) = Scanl a6989586621679545226 a6989586621679545227 a6989586621679545228

type family ScanlSym3 (a6989586621679545226 :: b ~> (a ~> b)) (a6989586621679545227 :: b) (a6989586621679545228 :: [a]) :: [b] where ... Source #

Equations

ScanlSym3 (a6989586621679545226 :: b ~> (a ~> b)) (a6989586621679545227 :: b) (a6989586621679545228 :: [a]) = Scanl a6989586621679545226 a6989586621679545227 a6989586621679545228 

data Scanl1Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> [a])) Source #

Instances

Instances details
SingI (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545217 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545217 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679545217

data Scanl1Sym1 (a6989586621679545217 :: a ~> (a ~> a)) (b :: TyFun [a] [a]) Source #

Instances

Instances details
SingI d => SingI (Scanl1Sym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanl1Sym1 d) #

SuppressUnusedWarnings (Scanl1Sym1 a6989586621679545217 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI1 (Scanl1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanl1Sym1 x) #

type Apply (Scanl1Sym1 a6989586621679545217 :: TyFun [a] [a] -> Type) (a6989586621679545218 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym1 a6989586621679545217 :: TyFun [a] [a] -> Type) (a6989586621679545218 :: [a]) = Scanl1 a6989586621679545217 a6989586621679545218

type family Scanl1Sym2 (a6989586621679545217 :: a ~> (a ~> a)) (a6989586621679545218 :: [a]) :: [a] where ... Source #

Equations

Scanl1Sym2 (a6989586621679545217 :: a ~> (a ~> a)) (a6989586621679545218 :: [a]) = Scanl1 a6989586621679545217 a6989586621679545218 

data ScanrSym0 (a1 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b]))) Source #

Instances

Instances details
SingI (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) #

SuppressUnusedWarnings (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545199 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679545199 :: a ~> (b ~> b)) = ScanrSym1 a6989586621679545199

data ScanrSym1 (a6989586621679545199 :: a ~> (b ~> b)) (b1 :: TyFun b ([a] ~> [b])) Source #

Instances

Instances details
SingI1 (ScanrSym1 :: (a ~> (b ~> b)) -> TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> b)). Sing x -> Sing (ScanrSym1 x) #

SingI d => SingI (ScanrSym1 d :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym1 d) #

SuppressUnusedWarnings (ScanrSym1 a6989586621679545199 :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym1 a6989586621679545199 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545200 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym1 a6989586621679545199 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679545200 :: b) = ScanrSym2 a6989586621679545199 a6989586621679545200

data ScanrSym2 (a6989586621679545199 :: a ~> (b ~> b)) (a6989586621679545200 :: b) (c :: TyFun [a] [b]) Source #

Instances

Instances details
SingI d => SingI1 (ScanrSym2 d :: b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: b). Sing x -> Sing (ScanrSym2 d x) #

SingI2 (ScanrSym2 :: (a ~> (b ~> b)) -> b -> TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> b)) (y :: b). Sing x -> Sing y -> Sing (ScanrSym2 x y) #

(SingI d1, SingI d2) => SingI (ScanrSym2 d1 d2 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ScanrSym2 d1 d2) #

SuppressUnusedWarnings (ScanrSym2 a6989586621679545199 a6989586621679545200 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym2 a6989586621679545199 a6989586621679545200 :: TyFun [a] [b] -> Type) (a6989586621679545201 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym2 a6989586621679545199 a6989586621679545200 :: TyFun [a] [b] -> Type) (a6989586621679545201 :: [a]) = Scanr a6989586621679545199 a6989586621679545200 a6989586621679545201

type family ScanrSym3 (a6989586621679545199 :: a ~> (b ~> b)) (a6989586621679545200 :: b) (a6989586621679545201 :: [a]) :: [b] where ... Source #

Equations

ScanrSym3 (a6989586621679545199 :: a ~> (b ~> b)) (a6989586621679545200 :: b) (a6989586621679545201 :: [a]) = Scanr a6989586621679545199 a6989586621679545200 a6989586621679545201 

data Scanr1Sym0 (a1 :: TyFun (a ~> (a ~> a)) ([a] ~> [a])) Source #

Instances

Instances details
SingI (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545179 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679545179 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679545179

data Scanr1Sym1 (a6989586621679545179 :: a ~> (a ~> a)) (b :: TyFun [a] [a]) Source #

Instances

Instances details
SingI d => SingI (Scanr1Sym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Scanr1Sym1 d) #

SuppressUnusedWarnings (Scanr1Sym1 a6989586621679545179 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI1 (Scanr1Sym1 :: (a ~> (a ~> a)) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (a ~> a)). Sing x -> Sing (Scanr1Sym1 x) #

type Apply (Scanr1Sym1 a6989586621679545179 :: TyFun [a] [a] -> Type) (a6989586621679545180 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym1 a6989586621679545179 :: TyFun [a] [a] -> Type) (a6989586621679545180 :: [a]) = Scanr1 a6989586621679545179 a6989586621679545180

type family Scanr1Sym2 (a6989586621679545179 :: a ~> (a ~> a)) (a6989586621679545180 :: [a]) :: [a] where ... Source #

Equations

Scanr1Sym2 (a6989586621679545179 :: a ~> (a ~> a)) (a6989586621679545180 :: [a]) = Scanr1 a6989586621679545179 a6989586621679545180 

Infinite lists

data ReplicateSym0 (a1 :: TyFun Natural (a ~> [a])) Source #

Instances

Instances details
SingI (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) #

SuppressUnusedWarnings (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679544286 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679544286 :: Natural) = ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type

data ReplicateSym1 (a6989586621679544286 :: Natural) (b :: TyFun a [a]) Source #

Instances

Instances details
SingI1 (ReplicateSym1 :: Natural -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ReplicateSym1 x :: TyFun a [a] -> Type) #

SingI d => SingI (ReplicateSym1 d :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ReplicateSym1 d :: TyFun a [a] -> Type) #

SuppressUnusedWarnings (ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type) (a6989586621679544287 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym1 a6989586621679544286 :: TyFun a [a] -> Type) (a6989586621679544287 :: a) = Replicate a6989586621679544286 a6989586621679544287

type family ReplicateSym2 (a6989586621679544286 :: Natural) (a6989586621679544287 :: a) :: [a] where ... Source #

Equations

ReplicateSym2 a6989586621679544286 (a6989586621679544287 :: a) = Replicate a6989586621679544286 a6989586621679544287 

Sublists

data TakeSym0 (a1 :: TyFun Natural ([a] ~> [a])) Source #

Instances

Instances details
SingI (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544445 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544445 :: Natural) = TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type

data TakeSym1 (a6989586621679544445 :: Natural) (b :: TyFun [a] [a]) Source #

Instances

Instances details
SingI1 (TakeSym1 :: Natural -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (TakeSym1 x :: TyFun [a] [a] -> Type) #

SingI d => SingI (TakeSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeSym1 d :: TyFun [a] [a] -> Type) #

SuppressUnusedWarnings (TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type) (a6989586621679544446 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym1 a6989586621679544445 :: TyFun [a] [a] -> Type) (a6989586621679544446 :: [a]) = Take a6989586621679544445 a6989586621679544446

type family TakeSym2 (a6989586621679544445 :: Natural) (a6989586621679544446 :: [a]) :: [a] where ... Source #

Equations

TakeSym2 a6989586621679544445 (a6989586621679544446 :: [a]) = Take a6989586621679544445 a6989586621679544446 

data DropSym0 (a1 :: TyFun Natural ([a] ~> [a])) Source #

Instances

Instances details
SingI (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544432 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679544432 :: Natural) = DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type

data DropSym1 (a6989586621679544432 :: Natural) (b :: TyFun [a] [a]) Source #

Instances

Instances details
SingI1 (DropSym1 :: Natural -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (DropSym1 x :: TyFun [a] [a] -> Type) #

SingI d => SingI (DropSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropSym1 d :: TyFun [a] [a] -> Type) #

SuppressUnusedWarnings (DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type) (a6989586621679544433 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym1 a6989586621679544432 :: TyFun [a] [a] -> Type) (a6989586621679544433 :: [a]) = Drop a6989586621679544432 a6989586621679544433

type family DropSym2 (a6989586621679544432 :: Natural) (a6989586621679544433 :: [a]) :: [a] where ... Source #

Equations

DropSym2 a6989586621679544432 (a6989586621679544433 :: [a]) = Drop a6989586621679544432 a6989586621679544433 

data TakeWhileSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a])) Source #

Instances

Instances details
SingI (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544574 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544574 :: a ~> Bool) = TakeWhileSym1 a6989586621679544574

data TakeWhileSym1 (a6989586621679544574 :: a ~> Bool) (b :: TyFun [a] [a]) Source #

Instances

Instances details
SingI d => SingI (TakeWhileSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (TakeWhileSym1 d) #

SuppressUnusedWarnings (TakeWhileSym1 a6989586621679544574 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI1 (TakeWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (TakeWhileSym1 x) #

type Apply (TakeWhileSym1 a6989586621679544574 :: TyFun [a] [a] -> Type) (a6989586621679544575 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym1 a6989586621679544574 :: TyFun [a] [a] -> Type) (a6989586621679544575 :: [a]) = TakeWhile a6989586621679544574 a6989586621679544575

type family TakeWhileSym2 (a6989586621679544574 :: a ~> Bool) (a6989586621679544575 :: [a]) :: [a] where ... Source #

Equations

TakeWhileSym2 (a6989586621679544574 :: a ~> Bool) (a6989586621679544575 :: [a]) = TakeWhile a6989586621679544574 a6989586621679544575 

data DropWhileSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a])) Source #

Instances

Instances details
SingI (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544559 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544559 :: a ~> Bool) = DropWhileSym1 a6989586621679544559

data DropWhileSym1 (a6989586621679544559 :: a ~> Bool) (b :: TyFun [a] [a]) Source #

Instances

Instances details
SingI d => SingI (DropWhileSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileSym1 d) #

SuppressUnusedWarnings (DropWhileSym1 a6989586621679544559 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI1 (DropWhileSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (DropWhileSym1 x) #

type Apply (DropWhileSym1 a6989586621679544559 :: TyFun [a] [a] -> Type) (a6989586621679544560 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym1 a6989586621679544559 :: TyFun [a] [a] -> Type) (a6989586621679544560 :: [a]) = DropWhile a6989586621679544559 a6989586621679544560

type family DropWhileSym2 (a6989586621679544559 :: a ~> Bool) (a6989586621679544560 :: [a]) :: [a] where ... Source #

Equations

DropWhileSym2 (a6989586621679544559 :: a ~> Bool) (a6989586621679544560 :: [a]) = DropWhile a6989586621679544559 a6989586621679544560 

data DropWhileEndSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> [a])) Source #

Instances

Instances details
SingI (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) #

SuppressUnusedWarnings (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544538 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679544538 :: a ~> Bool) = DropWhileEndSym1 a6989586621679544538

data DropWhileEndSym1 (a6989586621679544538 :: a ~> Bool) (b :: TyFun [a] [a]) Source #

Instances

Instances details
SingI d => SingI (DropWhileEndSym1 d :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (DropWhileEndSym1 d) #

SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679544538 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI1 (DropWhileEndSym1 :: (a ~> Bool) -> TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (DropWhileEndSym1 x) #

type Apply (DropWhileEndSym1 a6989586621679544538 :: TyFun [a] [a] -> Type) (a6989586621679544539 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym1 a6989586621679544538 :: TyFun [a] [a] -> Type) (a6989586621679544539 :: [a]) = DropWhileEnd a6989586621679544538 a6989586621679544539

type family DropWhileEndSym2 (a6989586621679544538 :: a ~> Bool) (a6989586621679544539 :: [a]) :: [a] where ... Source #

Equations

DropWhileEndSym2 (a6989586621679544538 :: a ~> Bool) (a6989586621679544539 :: [a]) = DropWhileEnd a6989586621679544538 a6989586621679544539 

data SpanSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a]))) Source #

Instances

Instances details
SingI (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) #

SuppressUnusedWarnings (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544497 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544497 :: a ~> Bool) = SpanSym1 a6989586621679544497

data SpanSym1 (a6989586621679544497 :: a ~> Bool) (b :: TyFun [a] ([a], [a])) Source #

Instances

Instances details
SingI d => SingI (SpanSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SpanSym1 d) #

SuppressUnusedWarnings (SpanSym1 a6989586621679544497 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI1 (SpanSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (SpanSym1 x) #

type Apply (SpanSym1 a6989586621679544497 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544498 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym1 a6989586621679544497 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544498 :: [a]) = Span a6989586621679544497 a6989586621679544498

type family SpanSym2 (a6989586621679544497 :: a ~> Bool) (a6989586621679544498 :: [a]) :: ([a], [a]) where ... Source #

Equations

SpanSym2 (a6989586621679544497 :: a ~> Bool) (a6989586621679544498 :: [a]) = Span a6989586621679544497 a6989586621679544498 

data BreakSym0 (a1 :: TyFun (a ~> Bool) ([a] ~> ([a], [a]))) Source #

Instances

Instances details
SingI (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) #

SuppressUnusedWarnings (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544458 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679544458 :: a ~> Bool) = BreakSym1 a6989586621679544458

data BreakSym1 (a6989586621679544458 :: a ~> Bool) (b :: TyFun [a] ([a], [a])) Source #

Instances

Instances details
SingI d => SingI (BreakSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (BreakSym1 d) #

SuppressUnusedWarnings (BreakSym1 a6989586621679544458 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SingI1 (BreakSym1 :: (a ~> Bool) -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> Bool). Sing x -> Sing (BreakSym1 x) #

type Apply (BreakSym1 a6989586621679544458 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544459 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym1 a6989586621679544458 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544459 :: [a]) = Break a6989586621679544458 a6989586621679544459

type family BreakSym2 (a6989586621679544458 :: a ~> Bool) (a6989586621679544459 :: [a]) :: ([a], [a]) where ... Source #

Equations

BreakSym2 (a6989586621679544458 :: a ~> Bool) (a6989586621679544459 :: [a]) = Break a6989586621679544458 a6989586621679544459 

data SplitAtSym0 (a1 :: TyFun Natural ([a] ~> ([a], [a]))) Source #

Instances

Instances details
SingI (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) #

SuppressUnusedWarnings (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679544425 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679544425 :: Natural) = SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type

data SplitAtSym1 (a6989586621679544425 :: Natural) (b :: TyFun [a] ([a], [a])) Source #

Instances

Instances details
SingI1 (SplitAtSym1 :: Natural -> TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (SplitAtSym1 x :: TyFun [a] ([a], [a]) -> Type) #

SingI d => SingI (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (SplitAtSym1 d :: TyFun [a] ([a], [a]) -> Type) #

SuppressUnusedWarnings (SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544426 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym1 a6989586621679544425 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679544426 :: [a]) = SplitAt a6989586621679544425 a6989586621679544426

type family SplitAtSym2 (a6989586621679544425 :: Natural) (a6989586621679544426 :: [a]) :: ([a], [a]) where ... Source #

Equations

SplitAtSym2 a6989586621679544425 (a6989586621679544426 :: [a]) = SplitAt a6989586621679544425 a6989586621679544426 

Searching lists

data NotElemSym0 (a1 :: TyFun a (t a ~> Bool)) Source #

Instances

Instances details
(SFoldable t, SEq a) => SingI (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) #

SuppressUnusedWarnings (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922306 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621679922306 :: a) = NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type

data NotElemSym1 (a6989586621679922306 :: a) (b :: TyFun (t a) Bool) Source #

Instances

Instances details
(SFoldable t, SEq a) => SingI1 (NotElemSym1 :: a -> TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (NotElemSym1 x :: TyFun (t a) Bool -> Type) #

(SFoldable t, SEq a, SingI d) => SingI (NotElemSym1 d :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing (NotElemSym1 d :: TyFun (t a) Bool -> Type) #

SuppressUnusedWarnings (NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type) (a6989586621679922307 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621679922306 :: TyFun (t a) Bool -> Type) (a6989586621679922307 :: t a) = NotElem a6989586621679922306 a6989586621679922307

type family NotElemSym2 (a6989586621679922306 :: a) (a6989586621679922307 :: t a) :: Bool where ... Source #

Equations

NotElemSym2 (a6989586621679922306 :: a) (a6989586621679922307 :: t a) = NotElem a6989586621679922306 a6989586621679922307 

data LookupSym0 (a1 :: TyFun a ([(a, b)] ~> Maybe b)) Source #

Instances

Instances details
SEq a => SingI (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) #

SuppressUnusedWarnings (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679544349 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679544349 :: a) = LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type

data LookupSym1 (a6989586621679544349 :: a) (b1 :: TyFun [(a, b)] (Maybe b)) Source #

Instances

Instances details
SEq a => SingI1 (LookupSym1 :: a -> TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a). Sing x -> Sing (LookupSym1 x :: TyFun [(a, b)] (Maybe b) -> Type) #

(SEq a, SingI d) => SingI (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (LookupSym1 d :: TyFun [(a, b)] (Maybe b) -> Type) #

SuppressUnusedWarnings (LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679544350 :: [(a, b)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym1 a6989586621679544349 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679544350 :: [(a, b)]) = Lookup a6989586621679544349 a6989586621679544350

type family LookupSym2 (a6989586621679544349 :: a) (a6989586621679544350 :: [(a, b)]) :: Maybe b where ... Source #

Equations

LookupSym2 (a6989586621679544349 :: a) (a6989586621679544350 :: [(a, b)]) = Lookup a6989586621679544349 a6989586621679544350 

Zipping and unzipping lists

data ZipSym0 (a1 :: TyFun [a] ([b] ~> [(a, b)])) Source #

Instances

Instances details
SingI (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) #

SuppressUnusedWarnings (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679544986 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679544986 :: [a]) = ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type

data ZipSym1 (a6989586621679544986 :: [a]) (b1 :: TyFun [b] [(a, b)]) Source #

Instances

Instances details
SingI1 (ZipSym1 :: [a] -> TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipSym1 x :: TyFun [b] [(a, b)] -> Type) #

SingI d => SingI (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipSym1 d :: TyFun [b] [(a, b)] -> Type) #

SuppressUnusedWarnings (ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type) (a6989586621679544987 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym1 a6989586621679544986 :: TyFun [b] [(a, b)] -> Type) (a6989586621679544987 :: [b]) = Zip a6989586621679544986 a6989586621679544987

type family ZipSym2 (a6989586621679544986 :: [a]) (a6989586621679544987 :: [b]) :: [(a, b)] where ... Source #

Equations

ZipSym2 (a6989586621679544986 :: [a]) (a6989586621679544987 :: [b]) = Zip a6989586621679544986 a6989586621679544987 

data Zip3Sym0 (a1 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)]))) Source #

Instances

Instances details
SingI (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) #

SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679544974 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679544974 :: [a]) = Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type

data Zip3Sym1 (a6989586621679544974 :: [a]) (b1 :: TyFun [b] ([c] ~> [(a, b, c)])) Source #

Instances

Instances details
SingI1 (Zip3Sym1 :: [a] -> TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (Zip3Sym1 x :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) #

SingI d => SingI (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym1 d :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) #

SuppressUnusedWarnings (Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679544975 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym1 a6989586621679544974 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679544975 :: [b]) = Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type

data Zip3Sym2 (a6989586621679544974 :: [a]) (a6989586621679544975 :: [b]) (c1 :: TyFun [c] [(a, b, c)]) Source #

Instances

Instances details
SingI2 (Zip3Sym2 :: [a] -> [b] -> TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: [a]) (y :: [b]). Sing x -> Sing y -> Sing (Zip3Sym2 x y :: TyFun [c] [(a, b, c)] -> Type) #

SingI d => SingI1 (Zip3Sym2 d :: [b] -> TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [b]). Sing x -> Sing (Zip3Sym2 d x :: TyFun [c] [(a, b, c)] -> Type) #

(SingI d1, SingI d2) => SingI (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Zip3Sym2 d1 d2 :: TyFun [c] [(a, b, c)] -> Type) #

SuppressUnusedWarnings (Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679544976 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym2 a6989586621679544974 a6989586621679544975 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679544976 :: [c]) = Zip3 a6989586621679544974 a6989586621679544975 a6989586621679544976

type family Zip3Sym3 (a6989586621679544974 :: [a]) (a6989586621679544975 :: [b]) (a6989586621679544976 :: [c]) :: [(a, b, c)] where ... Source #

Equations

Zip3Sym3 (a6989586621679544974 :: [a]) (a6989586621679544975 :: [b]) (a6989586621679544976 :: [c]) = Zip3 a6989586621679544974 a6989586621679544975 a6989586621679544976 

data ZipWithSym0 (a1 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c]))) Source #

Instances

Instances details
SingI (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) #

SuppressUnusedWarnings (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679544962 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679544962 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621679544962

data ZipWithSym1 (a6989586621679544962 :: a ~> (b ~> c)) (b1 :: TyFun [a] ([b] ~> [c])) Source #

Instances

Instances details
SingI1 (ZipWithSym1 :: (a ~> (b ~> c)) -> TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> c)). Sing x -> Sing (ZipWithSym1 x) #

SingI d => SingI (ZipWithSym1 d :: TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym1 d) #

SuppressUnusedWarnings (ZipWithSym1 a6989586621679544962 :: TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym1 a6989586621679544962 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679544963 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym1 a6989586621679544962 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679544963 :: [a]) = ZipWithSym2 a6989586621679544962 a6989586621679544963

data ZipWithSym2 (a6989586621679544962 :: a ~> (b ~> c)) (a6989586621679544963 :: [a]) (c1 :: TyFun [b] [c]) Source #

Instances

Instances details
SingI d => SingI1 (ZipWithSym2 d :: [a] -> TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWithSym2 d x) #

SingI2 (ZipWithSym2 :: (a ~> (b ~> c)) -> [a] -> TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> c)) (y :: [a]). Sing x -> Sing y -> Sing (ZipWithSym2 x y) #

(SingI d1, SingI d2) => SingI (ZipWithSym2 d1 d2 :: TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWithSym2 d1 d2) #

SuppressUnusedWarnings (ZipWithSym2 a6989586621679544962 a6989586621679544963 :: TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym2 a6989586621679544962 a6989586621679544963 :: TyFun [b] [c] -> Type) (a6989586621679544964 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym2 a6989586621679544962 a6989586621679544963 :: TyFun [b] [c] -> Type) (a6989586621679544964 :: [b]) = ZipWith a6989586621679544962 a6989586621679544963 a6989586621679544964

type family ZipWithSym3 (a6989586621679544962 :: a ~> (b ~> c)) (a6989586621679544963 :: [a]) (a6989586621679544964 :: [b]) :: [c] where ... Source #

Equations

ZipWithSym3 (a6989586621679544962 :: a ~> (b ~> c)) (a6989586621679544963 :: [a]) (a6989586621679544964 :: [b]) = ZipWith a6989586621679544962 a6989586621679544963 a6989586621679544964 

data ZipWith3Sym0 (a1 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d])))) Source #

Instances

Instances details
SingI (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) #

SuppressUnusedWarnings (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679544947 :: a ~> (b ~> (c ~> d))) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679544947 :: a ~> (b ~> (c ~> d))) = ZipWith3Sym1 a6989586621679544947

data ZipWith3Sym1 (a6989586621679544947 :: a ~> (b ~> (c ~> d))) (b1 :: TyFun [a] ([b] ~> ([c] ~> [d]))) Source #

Instances

Instances details
SingI1 (ZipWith3Sym1 :: (a ~> (b ~> (c ~> d))) -> TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: a ~> (b ~> (c ~> d))). Sing x -> Sing (ZipWith3Sym1 x) #

SingI d2 => SingI (ZipWith3Sym1 d2 :: TyFun [a] ([b] ~> ([c] ~> [d1])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym1 d2) #

SuppressUnusedWarnings (ZipWith3Sym1 a6989586621679544947 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym1 a6989586621679544947 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679544948 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym1 a6989586621679544947 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679544948 :: [a]) = ZipWith3Sym2 a6989586621679544947 a6989586621679544948

data ZipWith3Sym2 (a6989586621679544947 :: a ~> (b ~> (c ~> d))) (a6989586621679544948 :: [a]) (c1 :: TyFun [b] ([c] ~> [d])) Source #

Instances

Instances details
SingI d2 => SingI1 (ZipWith3Sym2 d2 :: [a] -> TyFun [b] ([c] ~> [d1]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ZipWith3Sym2 d2 x) #

SingI2 (ZipWith3Sym2 :: (a ~> (b ~> (c ~> d))) -> [a] -> TyFun [b] ([c] ~> [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: a ~> (b ~> (c ~> d))) (y :: [a]). Sing x -> Sing y -> Sing (ZipWith3Sym2 x y) #

(SingI d2, SingI d3) => SingI (ZipWith3Sym2 d2 d3 :: TyFun [b] ([c] ~> [d1]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym2 d2 d3) #

SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679544947 a6989586621679544948 :: TyFun [b] ([c] ~> [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym2 a6989586621679544947 a6989586621679544948 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679544949 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym2 a6989586621679544947 a6989586621679544948 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679544949 :: [b]) = ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949

data ZipWith3Sym3 (a6989586621679544947 :: a ~> (b ~> (c ~> d))) (a6989586621679544948 :: [a]) (a6989586621679544949 :: [b]) (d1 :: TyFun [c] [d]) Source #

Instances

Instances details
SingI d2 => SingI2 (ZipWith3Sym3 d2 :: [a] -> [b] -> TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing2 :: forall (x :: [a]) (y :: [b]). Sing x -> Sing y -> Sing (ZipWith3Sym3 d2 x y) #

(SingI d2, SingI d3) => SingI1 (ZipWith3Sym3 d2 d3 :: [b] -> TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

liftSing :: forall (x :: [b]). Sing x -> Sing (ZipWith3Sym3 d2 d3 x) #

(SingI d2, SingI d3, SingI d4) => SingI (ZipWith3Sym3 d2 d3 d4 :: TyFun [c] [d1] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (ZipWith3Sym3 d2 d3 d4) #

SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949 :: TyFun [c] [d] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949 :: TyFun [c] [d] -> Type) (a6989586621679544950 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym3 a6989586621679544947 a6989586621679544948 a6989586621679544949 :: TyFun [c] [d] -> Type) (a6989586621679544950 :: [c]) = ZipWith3 a6989586621679544947 a6989586621679544948 a6989586621679544949 a6989586621679544950

data UnzipSym0 (a1 :: TyFun [(a, b)] ([a], [b])) Source #

Instances

Instances details
SingI (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) #

SuppressUnusedWarnings (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679544929 :: [(a, b)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679544929 :: [(a, b)]) = Unzip a6989586621679544929

type family UnzipSym1 (a6989586621679544929 :: [(a, b)]) :: ([a], [b]) where ... Source #

Equations

UnzipSym1 (a6989586621679544929 :: [(a, b)]) = Unzip a6989586621679544929 

data Unzip3Sym0 (a1 :: TyFun [(a, b, c)] ([a], [b], [c])) Source #

Instances

Instances details
SingI (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

Methods

sing :: Sing (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) #

SuppressUnusedWarnings (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679544912 :: [(a, b, c)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679544912 :: [(a, b, c)]) = Unzip3 a6989586621679544912

type family Unzip3Sym1 (a6989586621679544912 :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #

Equations

Unzip3Sym1 (a6989586621679544912 :: [(a, b, c)]) = Unzip3 a6989586621679544912 

Functions on Symbols

data UnlinesSym0 (a :: TyFun [Symbol] Symbol) Source #

Instances

Instances details
SingI UnlinesSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings UnlinesSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnlinesSym0 (a6989586621679544819 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnlinesSym0 (a6989586621679544819 :: [Symbol]) = Unlines a6989586621679544819

type family UnlinesSym1 (a6989586621679544819 :: [Symbol]) :: Symbol where ... Source #

Equations

UnlinesSym1 a6989586621679544819 = Unlines a6989586621679544819 

data UnwordsSym0 (a :: TyFun [Symbol] Symbol) Source #

Instances

Instances details
SingI UnwordsSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings UnwordsSym0 Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnwordsSym0 (a6989586621679544809 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnwordsSym0 (a6989586621679544809 :: [Symbol]) = Unwords a6989586621679544809

type family UnwordsSym1 (a6989586621679544809 :: [Symbol]) :: Symbol where ... Source #

Equations

UnwordsSym1 a6989586621679544809 = Unwords a6989586621679544809 

Converting to and from Symbol

Converting to Symbol

data ShowsPrecSym0 (a1 :: TyFun Natural (a ~> (Symbol ~> Symbol))) Source #

Instances

Instances details
SShow a => SingI (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807409 :: Natural) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679807409 :: Natural) = ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type

data ShowsPrecSym1 (a6989586621679807409 :: Natural) (b :: TyFun a (Symbol ~> Symbol)) Source #

Instances

Instances details
SShow a => SingI1 (ShowsPrecSym1 :: Natural -> TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ShowsPrecSym1 x :: TyFun a (Symbol ~> Symbol) -> Type) #

(SShow a, SingI d) => SingI (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) #

SuppressUnusedWarnings (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807410 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621679807409 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807410 :: a) = ShowsPrecSym2 a6989586621679807409 a6989586621679807410

data ShowsPrecSym2 (a6989586621679807409 :: Natural) (a6989586621679807410 :: a) (c :: TyFun Symbol Symbol) Source #

Instances

Instances details
SShow a => SingI2 (ShowsPrecSym2 :: Natural -> a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Natural) (y :: a). Sing x -> Sing y -> Sing (ShowsPrecSym2 x y) #

(SShow a, SingI d) => SingI1 (ShowsPrecSym2 d :: a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsPrecSym2 d x) #

(SShow a, SingI d1, SingI d2) => SingI (ShowsPrecSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym2 d1 d2) #

SuppressUnusedWarnings (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) (a6989586621679807411 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621679807409 a6989586621679807410 :: TyFun Symbol Symbol -> Type) (a6989586621679807411 :: Symbol) = ShowsPrec a6989586621679807409 a6989586621679807410 a6989586621679807411

type family ShowsPrecSym3 (a6989586621679807409 :: Natural) (a6989586621679807410 :: a) (a6989586621679807411 :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrecSym3 a6989586621679807409 (a6989586621679807410 :: a) a6989586621679807411 = ShowsPrec a6989586621679807409 a6989586621679807410 a6989586621679807411 

data ShowListSym0 (a1 :: TyFun [a] (Symbol ~> Symbol)) Source #

Instances

Instances details
SShow a => SingI (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) #

SuppressUnusedWarnings (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807418 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621679807418 :: [a]) = ShowListSym1 a6989586621679807418

data ShowListSym1 (a6989586621679807418 :: [a]) (b :: TyFun Symbol Symbol) Source #

Instances

Instances details
SShow a => SingI1 (ShowListSym1 :: [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListSym1 x) #

(SShow a, SingI d) => SingI (ShowListSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym1 d) #

SuppressUnusedWarnings (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) (a6989586621679807419 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621679807418 :: TyFun Symbol Symbol -> Type) (a6989586621679807419 :: Symbol) = ShowList a6989586621679807418 a6989586621679807419

type family ShowListSym2 (a6989586621679807418 :: [a]) (a6989586621679807419 :: Symbol) :: Symbol where ... Source #

Equations

ShowListSym2 (a6989586621679807418 :: [a]) a6989586621679807419 = ShowList a6989586621679807418 a6989586621679807419 

data Show_Sym0 (a1 :: TyFun a Symbol) Source #

Instances

Instances details
SShow a => SingI (Show_Sym0 :: TyFun a Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (Show_Sym0 :: TyFun a Symbol -> Type) #

SuppressUnusedWarnings (Show_Sym0 :: TyFun a Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621679807414 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621679807414 :: a) = Show_ a6989586621679807414

type family Show_Sym1 (a6989586621679807414 :: a) :: Symbol where ... Source #

Equations

Show_Sym1 (a6989586621679807414 :: a) = Show_ a6989586621679807414 

data ShowsSym0 (a1 :: TyFun a (Symbol ~> Symbol)) Source #

Instances

Instances details
SShow a => SingI (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) #

SuppressUnusedWarnings (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807401 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621679807401 :: a) = ShowsSym1 a6989586621679807401

data ShowsSym1 (a6989586621679807401 :: a) (b :: TyFun Symbol Symbol) Source #

Instances

Instances details
SShow a => SingI1 (ShowsSym1 :: a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsSym1 x) #

(SShow a, SingI d) => SingI (ShowsSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym1 d) #

SuppressUnusedWarnings (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) (a6989586621679807402 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621679807401 :: TyFun Symbol Symbol -> Type) (a6989586621679807402 :: Symbol) = Shows a6989586621679807401 a6989586621679807402

type family ShowsSym2 (a6989586621679807401 :: a) (a6989586621679807402 :: Symbol) :: Symbol where ... Source #

Equations

ShowsSym2 (a6989586621679807401 :: a) a6989586621679807402 = Shows a6989586621679807401 a6989586621679807402 

data ShowCharSym0 (a :: TyFun Char (Symbol ~> Symbol)) Source #

Instances

Instances details
SingI ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621679807375 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621679807375 :: Char) = ShowCharSym1 a6989586621679807375

data ShowCharSym1 (a6989586621679807375 :: Char) (b :: TyFun Symbol Symbol) Source #

Instances

Instances details
SingI1 ShowCharSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Char). Sing x -> Sing (ShowCharSym1 x) #

SingI d => SingI (ShowCharSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowCharSym1 d) #

SuppressUnusedWarnings (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) (a6989586621679807376 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621679807375 :: TyFun Symbol Symbol -> Type) (a6989586621679807376 :: Symbol) = ShowChar a6989586621679807375 a6989586621679807376

type family ShowCharSym2 (a6989586621679807375 :: Char) (a6989586621679807376 :: Symbol) :: Symbol where ... Source #

Equations

ShowCharSym2 a6989586621679807375 a6989586621679807376 = ShowChar a6989586621679807375 a6989586621679807376 

data ShowStringSym0 (a :: TyFun Symbol (Symbol ~> Symbol)) Source #

Instances

Instances details
SingI ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621679807364 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621679807364 :: Symbol) = ShowStringSym1 a6989586621679807364

data ShowStringSym1 (a6989586621679807364 :: Symbol) (b :: TyFun Symbol Symbol) Source #

Instances

Instances details
SingI1 ShowStringSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol). Sing x -> Sing (ShowStringSym1 x) #

SingI d => SingI (ShowStringSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowStringSym1 d) #

SuppressUnusedWarnings (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) (a6989586621679807365 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621679807364 :: TyFun Symbol Symbol -> Type) (a6989586621679807365 :: Symbol) = ShowString a6989586621679807364 a6989586621679807365

type family ShowStringSym2 (a6989586621679807364 :: Symbol) (a6989586621679807365 :: Symbol) :: Symbol where ... Source #

Equations

ShowStringSym2 a6989586621679807364 a6989586621679807365 = ShowString a6989586621679807364 a6989586621679807365 

data ShowParenSym0 (a :: TyFun Bool ((Symbol ~> Symbol) ~> (Symbol ~> Symbol))) Source #

Instances

Instances details
SingI ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowParenSym0 (a6989586621679807346 :: Bool) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowParenSym0 (a6989586621679807346 :: Bool) = ShowParenSym1 a6989586621679807346

data ShowParenSym1 (a6989586621679807346 :: Bool) (b :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol)) Source #

Instances

Instances details
SingI1 ShowParenSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (ShowParenSym1 x) #

SingI d => SingI (ShowParenSym1 d :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym1 d) #

SuppressUnusedWarnings (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621679807347 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621679807346 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621679807347 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621679807346 a6989586621679807347

data ShowParenSym2 (a6989586621679807346 :: Bool) (a6989586621679807347 :: Symbol ~> Symbol) (c :: TyFun Symbol Symbol) Source #

Instances

Instances details
SingI2 ShowParenSym2 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Bool) (y :: Symbol ~> Symbol). Sing x -> Sing y -> Sing (ShowParenSym2 x y) #

(SingI d1, SingI d2) => SingI (ShowParenSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym2 d1 d2) #

SuppressUnusedWarnings (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SingI d => SingI1 (ShowParenSym2 d :: (Symbol ~> Symbol) -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol ~> Symbol). Sing x -> Sing (ShowParenSym2 d x) #

type Apply (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) (a6989586621679807348 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym2 a6989586621679807346 a6989586621679807347 :: TyFun Symbol Symbol -> Type) (a6989586621679807348 :: Symbol) = ShowParen a6989586621679807346 a6989586621679807347 a6989586621679807348