singletons-base-3.3: A promoted and singled version of the base library
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

data family TyCon :: (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 ~> k5) (x :: k1) 
Instance details

Defined in Data.Singletons

type Apply (TyCon f :: k1 ~> k5) (x :: k1) = ApplyTyCon f @@ x

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.Generics

Associated Types

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" '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 #

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

Defined in Data.Proxy.Singletons

PMonadPlus (Proxy :: k -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

MonadZip (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in 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 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 #

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 #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in 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) #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in 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 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 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 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 Data.Proxy

Methods

mzero :: Proxy a #

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

NFData1 (Proxy :: Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

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

Defined in Data.Proxy.Singletons

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Data.Proxy.Singletons

type Pure (a :: k1)
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)
SAlternative (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

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

(%<|>) :: forall a (t1 :: Proxy a) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<|>@#@$) :: TyFun (Proxy a) (Proxy a ~> Proxy a) -> Type) t1) t2) Source #

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

Defined in Data.Proxy.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Proxy a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Proxy (a ~> b)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Proxy (a ~> b)) (Proxy a ~> Proxy b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Proxy a ~> (Proxy b ~> Proxy c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Proxy a ~> Proxy b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Proxy b ~> Proxy a) -> Type) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Proxy a) ((a ~> Proxy b) ~> Proxy b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Proxy a) -> Type) t) Source #

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

Defined in Data.Proxy.Singletons

Methods

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

sMplus :: forall a (t1 :: Proxy a) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MplusSym0 :: TyFun (Proxy a) (Proxy a ~> Proxy a) -> Type) 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 (Apply (Apply (MzipSym0 :: TyFun (Proxy a) (Proxy b ~> Proxy (a, b)) -> Type) 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 (Apply (Apply (Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (Proxy a ~> (Proxy b ~> Proxy c)) -> Type) t1) t2) t3) Source #

sMunzip :: forall a b (t :: Proxy (a, b)). Sing t -> Sing (Apply (MunzipSym0 :: TyFun (Proxy (a, b)) (Proxy a, Proxy b) -> Type) t) Source #

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

Defined in Data.Foldable.Singletons

Associated Types

type Fold (a :: Proxy k2) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2)
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 (a1 :: k1) (a2 :: Proxy k1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a1 :: k1) (a2 :: Proxy k1)
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 (a :: Proxy k2) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a :: Proxy k2)
type Product (a :: Proxy k2) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a :: Proxy k2)
SFoldable (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Proxy m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Proxy m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Proxy a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Proxy a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Proxy a ~> b)) -> Type) t1) t2) t3) Source #

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

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Proxy a ~> b)) -> Type) t1) t2) t3) Source #

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

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Proxy a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Proxy a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Proxy a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Proxy a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Proxy a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Proxy a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Proxy a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Proxy a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Proxy a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Proxy a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Proxy a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Proxy a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Proxy a) a -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Proxy a ~> f (Proxy b)) -> Type) t1) t2) Source #

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

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

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

Data t => Data (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Proxy t -> c (Proxy t) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Proxy t) #

toConstr :: Proxy t -> Constr #

dataTypeOf :: Proxy t -> DataType #

dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Proxy t)) #

dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Proxy t)) #

gmapT :: (forall b. Data b => b -> b) -> Proxy t -> Proxy t #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Proxy t -> r #

gmapQ :: (forall d. Data d => d -> u) -> Proxy t -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Proxy t -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Proxy t -> m (Proxy t) #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in 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 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 Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in 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.Generics

Associated Types

type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" '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 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 Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

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

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in 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 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 #

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 (Apply (Apply ((==@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) 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 (MemptySym0 :: Proxy s) Source #

sMappend :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Proxy s]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Proxy s] (Proxy s) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Proxy s) (Proxy s ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Proxy s)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Proxy s)) (Proxy s) -> Type) 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 (Apply (SuccSym0 :: TyFun (Proxy s) (Proxy s) -> Type) t) Source #

sPred :: forall (t :: Proxy s). Sing t -> Sing (Apply (PredSym0 :: TyFun (Proxy s) (Proxy s) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (Proxy s) -> Type) t) Source #

sFromEnum :: forall (t :: Proxy s). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (Proxy s) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (Proxy s) (Proxy s ~> [Proxy s]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Proxy s) (t2 :: Proxy s) (t3 :: Proxy s). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Proxy s) (Proxy s ~> (Proxy s ~> [Proxy s])) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Proxy s ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Proxy s). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Proxy s) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Proxy s]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Proxy s] (Symbol ~> Symbol) -> Type) 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 ~> k2) (a3 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (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 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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.Generics

type Rep1 (Proxy :: k -> Type) = D1 ('MetaData "Proxy" "Data.Proxy" "base" 'False) (C1 ('MetaCons "Proxy" 'PrefixI 'False) (U1 :: k -> Type))
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 Pure (a :: k1) Source # 
Instance details

Defined in Data.Proxy.Singletons

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

Defined in Data.Proxy.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Proxy.Singletons

type (arg :: a) <$ (arg1 :: Proxy b)
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 Fold (a :: Proxy k2) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Fold (a :: Proxy k2)
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 (a :: Proxy k2) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Product (a :: Proxy k2)
type Sum (a :: Proxy k2) Source # 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type ToList (arg :: 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.Generics

type Rep (Proxy t) = D1 ('MetaData "Proxy" "Data.Proxy" "base" '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

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

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 ('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 ('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 ('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 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 XorSym0 Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing XorSym0 #

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

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

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

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

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

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

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

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

SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromMaybeSym1 d) #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(SingI n1, SingI n2) => SingI ('(n1, n2) :: (a, b)) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

Methods

sing :: Sing '(n1, n2) #

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

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

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

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

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

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

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

(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, 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) #

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 x => SingI (PairSym1 x :: TyFun (g a) (Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sing :: Sing (PairSym1 x :: TyFun (g a) (Product f g a) -> 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) #

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 a2 => SingI ('Const a2 :: Const a1 b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sing :: Sing ('Const a2 :: Const a1 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 x => SingI ('InL x :: Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sing :: Sing ('InL x :: Sum f g a) #

SingI y => SingI ('InR y :: Sum f g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Methods

sing :: Sing ('InR y :: Sum f g a) #

(SingI x, SingI y) => SingI ('Pair x y :: Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sing :: Sing ('Pair x y) #

(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 x => SingI ('Compose x :: Compose f g a) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Methods

sing :: Sing ('Compose x) #

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

type family Sing :: k -> Type #

Instances

Instances details
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 = SVoid
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 Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

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.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 = 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.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 = SNonEmpty :: NonEmpty 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.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 Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Sing = SArg :: Arg a b -> 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

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

data SomeSing k where #

Constructors

SomeSing :: forall k (a :: k). Sing a -> SomeSing k 

Instances

Instances details
SIsString k => IsString (SomeSing k) Source # 
Instance details

Defined in Data.Singletons.Base.SomeSing

Methods

fromString :: String -> SomeSing k #

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 #

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 #

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

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

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 (@@@#@$) (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 (a6989586621679687550 :: All) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply GetAllSym0 (a6989586621679687550 :: All) = GetAll a6989586621679687550
type Apply GetAnySym0 (a6989586621679687566 :: Any) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply GetAnySym0 (a6989586621679687566 :: Any) = GetAny a6989586621679687566
type Apply KnownNatSym0 (a6989586621679566098 :: Nat) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply KnownNatSym0 (a6989586621679566098 :: Nat) = KnownNat a6989586621679566098
type Apply Log2Sym0 (a6989586621679566742 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply Log2Sym0 (a6989586621679566742 :: Natural) = Log2 a6989586621679566742
type Apply NatToCharSym0 (a6989586621679570244 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply NatToCharSym0 (a6989586621679570244 :: Natural) = NatToChar a6989586621679570244
type Apply AllSym0 (a6989586621679687547 :: Bool) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply AllSym0 (a6989586621679687547 :: Bool) = 'All a6989586621679687547
type Apply AnySym0 (a6989586621679687563 :: Bool) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply AnySym0 (a6989586621679687563 :: Bool) = 'Any a6989586621679687563
type Apply NotSym0 (a6989586621679132813 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply NotSym0 (a6989586621679132813 :: Bool) = Not a6989586621679132813
type Apply CharToNatSym0 (a6989586621679570020 :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply CharToNatSym0 (a6989586621679570020 :: Char) = CharToNat a6989586621679570020
type Apply KnownCharSym0 (a6989586621679566102 :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply KnownCharSym0 (a6989586621679566102 :: Char) = KnownChar a6989586621679566102
type Apply KnownSymbolSym0 (a6989586621679566100 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply KnownSymbolSym0 (a6989586621679566100 :: Symbol) = KnownSymbol a6989586621679566100
type Apply ShowCommaSpaceSym0 (a6989586621680208635 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCommaSpaceSym0 (a6989586621680208635 :: Symbol) = ShowCommaSpace a6989586621680208635
type Apply ShowSpaceSym0 (a6989586621680208641 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

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

Defined in Data.Singletons

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

Defined in Data.Void.Singletons

type Apply (AbsurdSym0 :: TyFun Void k2 -> Type) (a6989586621679178857 :: Void) = Absurd a6989586621679178857 :: k2
type Apply (TypeErrorSym0 :: TyFun PErrorMessage k2 -> Type) (a6989586621680205235 :: PErrorMessage) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply (TypeErrorSym0 :: TyFun PErrorMessage k2 -> Type) (a6989586621680205235 :: PErrorMessage) = TypeError a6989586621680205235 :: k2
type Apply (DivSym1 a6989586621679566965 :: TyFun Natural Natural -> Type) (a6989586621679566966 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (DivSym1 a6989586621679566965 :: TyFun Natural Natural -> Type) (a6989586621679566966 :: Natural) = Div a6989586621679566965 a6989586621679566966
type Apply (ModSym1 a6989586621679567401 :: TyFun Natural Natural -> Type) (a6989586621679567402 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (ModSym1 a6989586621679567401 :: TyFun Natural Natural -> Type) (a6989586621679567402 :: Natural) = Mod a6989586621679567401 a6989586621679567402
type Apply (QuotSym1 a6989586621679568006 :: TyFun Natural Natural -> Type) (a6989586621679568007 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (QuotSym1 a6989586621679568006 :: TyFun Natural Natural -> Type) (a6989586621679568007 :: Natural) = Quot a6989586621679568006 a6989586621679568007
type Apply (RemSym1 a6989586621679567995 :: TyFun Natural Natural -> Type) (a6989586621679567996 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (RemSym1 a6989586621679567995 :: TyFun Natural Natural -> Type) (a6989586621679567996 :: Natural) = Rem a6989586621679567995 a6989586621679567996
type Apply ((^@#@$$) a6989586621679556329 :: TyFun Natural Natural -> Type) (a6989586621679556330 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((^@#@$$) a6989586621679556329 :: TyFun Natural Natural -> Type) (a6989586621679556330 :: Natural) = a6989586621679556329 ^ a6989586621679556330
type Apply (ToEnumSym0 :: TyFun Natural k2 -> Type) (a6989586621679612929 :: Natural) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (ToEnumSym0 :: TyFun Natural k2 -> Type) (a6989586621679612929 :: Natural) = ToEnum a6989586621679612929 :: k2
type Apply (FromIntegerSym0 :: TyFun Natural k2 -> Type) (a6989586621679590965 :: Natural) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (FromIntegerSym0 :: TyFun Natural k2 -> Type) (a6989586621679590965 :: Natural) = FromInteger a6989586621679590965 :: k2
type Apply ((&&@#@$$) a6989586621679132115 :: TyFun Bool Bool -> Type) (a6989586621679132116 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((&&@#@$$) a6989586621679132115 :: TyFun Bool Bool -> Type) (a6989586621679132116 :: Bool) = a6989586621679132115 && a6989586621679132116
type Apply ((||@#@$$) a6989586621679132472 :: TyFun Bool Bool -> Type) (a6989586621679132473 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((||@#@$$) a6989586621679132472 :: TyFun Bool Bool -> Type) (a6989586621679132473 :: Bool) = a6989586621679132472 || a6989586621679132473
type Apply (ConsSymbolSym1 a6989586621679569296 :: TyFun Symbol Symbol -> Type) (a6989586621679569297 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (ConsSymbolSym1 a6989586621679569296 :: TyFun Symbol Symbol -> Type) (a6989586621679569297 :: Symbol) = ConsSymbol a6989586621679569296 a6989586621679569297
type Apply (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) (a6989586621680208681 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) (a6989586621680208681 :: Symbol) = ShowChar a6989586621680208680 a6989586621680208681
type Apply (ShowStringSym1 a6989586621680208669 :: TyFun Symbol Symbol -> Type) (a6989586621680208670 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621680208669 :: TyFun Symbol Symbol -> Type) (a6989586621680208670 :: Symbol) = ShowString a6989586621680208669 a6989586621680208670
type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (a6989586621681179965 :: Symbol) Source # 
Instance details

Defined in Data.String.Singletons

type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (a6989586621681179965 :: Symbol) = FromString a6989586621681179965 :: k2
type Apply (ErrorSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555664 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555664 :: Symbol) = Error a6989586621679555664 :: k2
type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555924 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555924 :: Symbol) = ErrorWithoutStackTrace a6989586621679555924 :: k2
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) (a6989586621679612932 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Text.Show.Singletons

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

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

Defined in GHC.Base.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in GHC.Num.Singletons

type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679590962 :: a) = Signum a6989586621679590962
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 ((!!@#@$$) a6989586621681120384 :: TyFun Natural a -> Type) (a6989586621681120385 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$$) a6989586621681120384 :: TyFun Natural a -> Type) (a6989586621681120385 :: Natural) = a6989586621681120384 !! a6989586621681120385
type Apply ((!!@#@$$) a6989586621679814661 :: TyFun Natural a -> Type) (a6989586621679814662 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$$) a6989586621679814661 :: TyFun Natural a -> Type) (a6989586621679814662 :: Natural) = a6989586621679814661 !! a6989586621679814662
type Apply (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) (a6989586621680208724 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) (a6989586621680208724 :: Symbol) = ShowList a6989586621680208723 a6989586621680208724
type Apply (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) (a6989586621680208655 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) (a6989586621680208655 :: Symbol) = ShowParen a6989586621680208653 a6989586621680208654 a6989586621680208655
type Apply (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) (a6989586621680208707 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) (a6989586621680208707 :: Symbol) = Shows a6989586621680208706 a6989586621680208707
type Apply (CompareSym1 a6989586621679237108 :: TyFun a Ordering -> Type) (a6989586621679237109 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym1 a6989586621679237108 :: TyFun a Ordering -> Type) (a6989586621679237109 :: a) = Compare a6989586621679237108 a6989586621679237109
type Apply ((/=@#@$$) a6989586621679137923 :: TyFun a Bool -> Type) (a6989586621679137924 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$$) a6989586621679137923 :: TyFun a Bool -> Type) (a6989586621679137924 :: a) = a6989586621679137923 /= a6989586621679137924
type Apply ((==@#@$$) a6989586621679137918 :: TyFun a Bool -> Type) (a6989586621679137919 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$$) a6989586621679137918 :: TyFun a Bool -> Type) (a6989586621679137919 :: a) = a6989586621679137918 == a6989586621679137919
type Apply ((<=@#@$$) a6989586621679237118 :: TyFun a Bool -> Type) (a6989586621679237119 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$$) a6989586621679237118 :: TyFun a Bool -> Type) (a6989586621679237119 :: a) = a6989586621679237118 <= a6989586621679237119
type Apply ((<@#@$$) a6989586621679237113 :: TyFun a Bool -> Type) (a6989586621679237114 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$$) a6989586621679237113 :: TyFun a Bool -> Type) (a6989586621679237114 :: a) = a6989586621679237113 < a6989586621679237114
type Apply ((>=@#@$$) a6989586621679237128 :: TyFun a Bool -> Type) (a6989586621679237129 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$$) a6989586621679237128 :: TyFun a Bool -> Type) (a6989586621679237129 :: a) = a6989586621679237128 >= a6989586621679237129
type Apply ((>@#@$$) a6989586621679237123 :: TyFun a Bool -> Type) (a6989586621679237124 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$$) a6989586621679237123 :: TyFun a Bool -> Type) (a6989586621679237124 :: a) = a6989586621679237123 > a6989586621679237124
type Apply (MappendSym1 a6989586621680292326 :: TyFun a a -> Type) (a6989586621680292327 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym1 a6989586621680292326 :: TyFun a a -> Type) (a6989586621680292327 :: a) = Mappend a6989586621680292326 a6989586621680292327
type Apply (MaxSym1 a6989586621679237133 :: TyFun a a -> Type) (a6989586621679237134 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym1 a6989586621679237133 :: TyFun a a -> Type) (a6989586621679237134 :: a) = Max a6989586621679237133 a6989586621679237134
type Apply (MinSym1 a6989586621679237138 :: TyFun a a -> Type) (a6989586621679237139 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym1 a6989586621679237138 :: TyFun a a -> Type) (a6989586621679237139 :: a) = Min a6989586621679237138 a6989586621679237139
type Apply ((<>@#@$$) a6989586621679207889 :: TyFun a a -> Type) (a6989586621679207890 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$$) a6989586621679207889 :: TyFun a a -> Type) (a6989586621679207890 :: a) = a6989586621679207889 <> a6989586621679207890
type Apply (AsTypeOfSym1 a6989586621679180187 :: TyFun a a -> Type) (a6989586621679180188 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym1 a6989586621679180187 :: TyFun a a -> Type) (a6989586621679180188 :: a) = AsTypeOf a6989586621679180187 a6989586621679180188
type Apply ((*@#@$$) a6989586621679590952 :: TyFun a a -> Type) (a6989586621679590953 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$$) a6989586621679590952 :: TyFun a a -> Type) (a6989586621679590953 :: a) = a6989586621679590952 * a6989586621679590953
type Apply ((+@#@$$) a6989586621679590942 :: TyFun a a -> Type) (a6989586621679590943 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$$) a6989586621679590942 :: TyFun a a -> Type) (a6989586621679590943 :: a) = a6989586621679590942 + a6989586621679590943
type Apply ((-@#@$$) a6989586621679590947 :: TyFun a a -> Type) (a6989586621679590948 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$$) a6989586621679590947 :: TyFun a a -> Type) (a6989586621679590948 :: a) = a6989586621679590947 - a6989586621679590948
type Apply (SubtractSym1 a6989586621679590935 :: TyFun a a -> Type) (a6989586621679590936 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym1 a6989586621679590935 :: TyFun a a -> Type) (a6989586621679590936 :: a) = Subtract a6989586621679590935 a6989586621679590936
type Apply (DefaultEqSym1 a6989586621679140066 :: TyFun k Bool -> Type) (a6989586621679140067 :: k) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply (DefaultEqSym1 a6989586621679140066 :: TyFun k Bool -> Type) (a6989586621679140067 :: k) = DefaultEq a6989586621679140066 a6989586621679140067
type Apply ((<=?@#@$$) a6989586621679556760 :: TyFun k Bool -> Type) (a6989586621679556761 :: k) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((<=?@#@$$) a6989586621679556760 :: TyFun k Bool -> Type) (a6989586621679556761 :: k) = a6989586621679556760 <=? a6989586621679556761
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 a6989586621679130897 a6989586621679130898 :: TyFun Bool a -> Type) (a6989586621679130899 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (Bool_Sym2 a6989586621679130897 a6989586621679130898 :: TyFun Bool a -> Type) (a6989586621679130899 :: Bool) = Bool_ a6989586621679130897 a6989586621679130898 a6989586621679130899
type Apply (ShowListWithSym2 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) (a6989586621680208690 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym2 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) (a6989586621680208690 :: Symbol) = ShowListWith a6989586621680208688 a6989586621680208689 a6989586621680208690
type Apply (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) (a6989586621680208716 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) (a6989586621680208716 :: Symbol) = ShowsPrec a6989586621680208714 a6989586621680208715 a6989586621680208716
type Apply (UntilSym2 a6989586621679180149 a6989586621679180150 :: TyFun a a -> Type) (a6989586621679180151 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym2 a6989586621679180149 a6989586621679180150 :: TyFun a a -> Type) (a6989586621679180151 :: a) = Until a6989586621679180149 a6989586621679180150 a6989586621679180151
type Apply (($!@#@$$) a6989586621679180167 :: TyFun a b -> Type) (a6989586621679180168 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$$) a6989586621679180167 :: TyFun a b -> Type) (a6989586621679180168 :: a) = a6989586621679180167 $! a6989586621679180168
type Apply (($@#@$$) a6989586621679180176 :: TyFun a b -> Type) (a6989586621679180177 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$$) a6989586621679180176 :: TyFun a b -> Type) (a6989586621679180177 :: a) = a6989586621679180176 $ a6989586621679180177
type Apply (ConstSym1 a6989586621679180220 :: TyFun b a -> Type) (a6989586621679180221 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym1 a6989586621679180220 :: TyFun b a -> Type) (a6989586621679180221 :: b) = Const a6989586621679180220 a6989586621679180221
type Apply (SeqSym1 a6989586621679180140 :: TyFun b b -> Type) (a6989586621679180141 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym1 a6989586621679180140 :: TyFun b b -> Type) (a6989586621679180141 :: b) = Seq a6989586621679180140 a6989586621679180141
type Apply (IfSym2 a6989586621679133031 a6989586621679133032 :: TyFun k k -> Type) (a6989586621679133033 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym2 a6989586621679133031 a6989586621679133032 :: TyFun k k -> Type) (a6989586621679133033 :: k) = If a6989586621679133031 a6989586621679133032 a6989586621679133033
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 a6989586621679237099 a6989586621679237100 :: TyFun b Ordering -> Type) (a6989586621679237101 :: b) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym2 a6989586621679237099 a6989586621679237100 :: TyFun b Ordering -> Type) (a6989586621679237101 :: b) = Comparing a6989586621679237099 a6989586621679237100 a6989586621679237101
type Apply (TyCon f :: k1 ~> k5) (x :: k1) 
Instance details

Defined in Data.Singletons

type Apply (TyCon f :: k1 ~> k5) (x :: k1) = ApplyTyCon f @@ x
type Apply (a6989586621679180207 .@#@$$$ a6989586621679180208 :: TyFun a c -> Type) (a6989586621679180209 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (a6989586621679180207 .@#@$$$ a6989586621679180208 :: TyFun a c -> Type) (a6989586621679180209 :: a) = (a6989586621679180207 . a6989586621679180208) a6989586621679180209
type Apply (FlipSym2 a6989586621679180195 a6989586621679180196 :: TyFun a c -> Type) (a6989586621679180197 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym2 a6989586621679180195 a6989586621679180196 :: TyFun a c -> Type) (a6989586621679180197 :: a) = Flip a6989586621679180195 a6989586621679180196 a6989586621679180197
type Apply (CurrySym2 a6989586621679172893 a6989586621679172894 :: TyFun b c -> Type) (a6989586621679172895 :: b) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym2 a6989586621679172893 a6989586621679172894 :: TyFun b c -> Type) (a6989586621679172895 :: b) = Curry a6989586621679172893 a6989586621679172894 a6989586621679172895
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 a6989586621679327018 a6989586621679327019 a6989586621679327020 :: TyFun a c -> Type) (a6989586621679327021 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym3 a6989586621679327018 a6989586621679327019 a6989586621679327020 :: TyFun a c -> Type) (a6989586621679327021 :: a) = On a6989586621679327018 a6989586621679327019 a6989586621679327020 a6989586621679327021
type Apply UnconsSymbolSym0 (a6989586621679569801 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

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

Defined in Control.Monad.Singletons.Internal

type Apply (GuardSym0 :: TyFun Bool (f ()) -> Type) (a6989586621679348283 :: Bool) = Guard a6989586621679348283 :: f ()
type Apply (IdentitySym0 :: TyFun a (Identity a) -> Type) (a6989586621679047151 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Ord.Singletons

type Apply (DownSym0 :: TyFun a (Down a) -> Type) (a6989586621679248119 :: a) = 'Down a6989586621679248119
type Apply (FirstSym0 :: TyFun a (First a) -> Type) (a6989586621679687658 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (MinSym0 :: TyFun a (Min a) -> Type) (a6989586621679687620 :: a) = 'Min a6989586621679687620
type Apply (DualSym0 :: TyFun a (Dual a) -> Type) (a6989586621679687531 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Singletons.Base.TypeError

type Apply (TextSym0 :: TyFun s (ErrorMessage' s) -> Type) (a6989586621680205225 :: s) = 'Text a6989586621680205225
type Apply (ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type) (a6989586621679814682 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type) (a6989586621679814682 :: a) = Replicate a6989586621679814681 a6989586621679814682
type Apply (EnumFromToSym1 a6989586621679612936 :: TyFun a [a] -> Type) (a6989586621679612937 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym1 a6989586621679612936 :: TyFun a [a] -> Type) (a6989586621679612937 :: a) = EnumFromTo a6989586621679612936 a6989586621679612937
type Apply (PureSym0 :: TyFun a (f a) -> Type) (a6989586621679348508 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

Defined in Control.Monad.Singletons.Internal

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

Defined in Data.Singletons.Base.TypeError

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

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldSym1 a6989586621681120784 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120785 :: a) = Unfold a6989586621681120784 a6989586621681120785
type Apply (UnfoldrSym1 a6989586621681120749 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120750 :: a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnfoldrSym1 a6989586621681120749 :: TyFun a (NonEmpty b) -> Type) (a6989586621681120750 :: a) = Unfoldr a6989586621681120749 a6989586621681120750
type Apply (EnumFromThenToSym2 a6989586621679612942 a6989586621679612943 :: TyFun a [a] -> Type) (a6989586621679612944 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym2 a6989586621679612942 a6989586621679612943 :: TyFun a [a] -> Type) (a6989586621679612944 :: a) = EnumFromThenTo a6989586621679612942 a6989586621679612943 a6989586621679612944
type Apply (UnfoldrSym1 a6989586621679815436 :: TyFun b [a] -> Type) (a6989586621679815437 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnfoldrSym1 a6989586621679815436 :: TyFun b [a] -> Type) (a6989586621679815437 :: b) = Unfoldr a6989586621679815436 a6989586621679815437
type Apply (($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type) (a6989586621679532902 :: b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type) (a6989586621679532902 :: b) = a6989586621679532901 $> a6989586621679532902
type Apply (a6989586621681205338 <=<@#@$$$ a6989586621681205339 :: TyFun a (m c) -> Type) (a6989586621681205340 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (a6989586621681205338 <=<@#@$$$ a6989586621681205339 :: TyFun a (m c) -> Type) (a6989586621681205340 :: a) = (a6989586621681205338 <=< a6989586621681205339) a6989586621681205340
type Apply (a6989586621681205350 >=>@#@$$$ a6989586621681205351 :: TyFun a (m c) -> Type) (a6989586621681205352 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (a6989586621681205350 >=>@#@$$$ a6989586621681205351 :: TyFun a (m c) -> Type) (a6989586621681205352 :: a) = (a6989586621681205350 >=> a6989586621681205351) a6989586621681205352
type Apply DivSym0 (a6989586621679566965 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply DivSym0 (a6989586621679566965 :: Natural) = DivSym1 a6989586621679566965
type Apply ModSym0 (a6989586621679567401 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply ModSym0 (a6989586621679567401 :: Natural) = ModSym1 a6989586621679567401
type Apply QuotSym0 (a6989586621679568006 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply QuotSym0 (a6989586621679568006 :: Natural) = QuotSym1 a6989586621679568006
type Apply RemSym0 (a6989586621679567995 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

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

Defined in GHC.TypeLits.Singletons.Internal

type Apply (^@#@$) (a6989586621679556329 :: Natural) = (^@#@$$) a6989586621679556329
type Apply DivModSym0 (a6989586621679568024 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply DivModSym0 (a6989586621679568024 :: Natural) = DivModSym1 a6989586621679568024
type Apply QuotRemSym0 (a6989586621679568017 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply QuotRemSym0 (a6989586621679568017 :: Natural) = QuotRemSym1 a6989586621679568017
type Apply ShowParenSym0 (a6989586621680208653 :: Bool) Source # 
Instance details

Defined in Text.Show.Singletons

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

Defined in Data.Bool.Singletons

type Apply (&&@#@$) (a6989586621679132115 :: Bool) = (&&@#@$$) a6989586621679132115
type Apply (||@#@$) (a6989586621679132472 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

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

Defined in GHC.TypeLits.Singletons

type Apply ConsSymbolSym0 (a6989586621679569296 :: Char) = ConsSymbolSym1 a6989586621679569296
type Apply ShowCharSym0 (a6989586621680208680 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621680208680 :: Char) = ShowCharSym1 a6989586621680208680
type Apply ShowStringSym0 (a6989586621680208669 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621680208669 :: Symbol) = ShowStringSym1 a6989586621680208669
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) (a6989586621681120576 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Text.Show.Singletons

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

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679814681 :: Natural) = ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type
type Apply (DivModSym1 a6989586621679568024 :: TyFun Natural (Natural, Natural) -> Type) (a6989586621679568025 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (DivModSym1 a6989586621679568024 :: TyFun Natural (Natural, Natural) -> Type) (a6989586621679568025 :: Natural) = DivMod a6989586621679568024 a6989586621679568025
type Apply (QuotRemSym1 a6989586621679568017 :: TyFun Natural (Natural, Natural) -> Type) (a6989586621679568018 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (QuotRemSym1 a6989586621679568017 :: TyFun Natural (Natural, Natural) -> Type) (a6989586621679568018 :: Natural) = QuotRem a6989586621679568017 a6989586621679568018
type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621681205232 :: Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

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

Defined in Control.Monad.Singletons.Internal

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

Defined in Data.Bool.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Singletons.Base.Instances

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

Defined in Text.Show.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Bool.Singletons

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in GHC.Base.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((<=?@#@$) :: TyFun k (k ~> Bool) -> Type) (a6989586621679556760 :: k) = (<=?@#@$$) a6989586621679556760
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) (a6989586621681205242 :: Natural) Source # 
Instance details

Defined in Control.Monad.Singletons

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

Defined in Control.Monad.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Function.Singletons

type Apply ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) (a6989586621679327005 :: a) = (&@#@$$) a6989586621679327005 :: TyFun (a ~> b) b -> Type
type Apply (Bool_Sym1 a6989586621679130897 :: TyFun a (Bool ~> a) -> Type) (a6989586621679130898 :: a) Source # 
Instance details

Defined in Data.Bool.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym1 a6989586621679815152 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815153 :: a) = DeleteBySym2 a6989586621679815152 a6989586621679815153
type Apply (InsertBySym1 a6989586621679815110 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815111 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym1 a6989586621679815110 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815111 :: a) = InsertBySym2 a6989586621679815110 a6989586621679815111
type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) = ShowsPrecSym2 a6989586621680208714 a6989586621680208715
type Apply (EnumFromThenToSym1 a6989586621679612942 :: TyFun a (a ~> [a]) -> Type) (a6989586621679612943 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679612942 :: TyFun a (a ~> [a]) -> Type) (a6989586621679612943 :: a) = EnumFromThenToSym2 a6989586621679612942 a6989586621679612943
type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680862528 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in GHC.Base.Singletons

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

Defined in GHC.Base.Singletons

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

Defined in Data.Proxy.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679577734 :: b) = Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type
type Apply (IfSym1 a6989586621679133031 :: TyFun k (k ~> k) -> Type) (a6989586621679133032 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym1 a6989586621679133031 :: TyFun k (k ~> k) -> Type) (a6989586621679133032 :: k) = IfSym2 a6989586621679133031 a6989586621679133032
type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679046760 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

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

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679348489 :: a) = (<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type
type Apply (ArgSym1 a6989586621680862528 :: TyFun b (Arg a b) -> Type) (a6989586621680862529 :: b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (ArgSym1 a6989586621680862528 :: TyFun b (Arg a b) -> Type) (a6989586621680862529 :: b) = 'Arg a6989586621680862528 a6989586621680862529
type Apply (ScanlSym1 a6989586621681120649 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120650 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym1 a6989586621681120649 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120650 :: b) = ScanlSym2 a6989586621681120649 a6989586621681120650
type Apply (ScanrSym1 a6989586621681120637 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120638 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym1 a6989586621681120637 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120638 :: b) = ScanrSym2 a6989586621681120637 a6989586621681120638
type Apply (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815592 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815592 :: b) = ScanlSym2 a6989586621679815591 a6989586621679815592
type Apply (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815565 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815565 :: b) = ScanrSym2 a6989586621679815564 a6989586621679815565
type Apply (ComparingSym1 a6989586621679237099 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679237100 :: b) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym1 a6989586621679237099 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679237100 :: b) = ComparingSym2 a6989586621679237099 a6989586621679237100
type Apply (Tuple2Sym1 a6989586621679046729 :: TyFun k2 (k1, k2) -> Type) (a6989586621679046730 :: k2) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym1 a6989586621679046729 :: TyFun k2 (k1, k2) -> Type) (a6989586621679046730 :: k2) = '(a6989586621679046729, a6989586621679046730)
type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679046809 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679046809 :: a) = Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type
type Apply (CurrySym1 a6989586621679172893 :: TyFun a (b ~> c) -> Type) (a6989586621679172894 :: a) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym1 a6989586621679172893 :: TyFun a (b ~> c) -> Type) (a6989586621679172894 :: a) = CurrySym2 a6989586621679172893 a6989586621679172894
type Apply (FlipSym1 a6989586621679180195 :: TyFun b (a ~> c) -> Type) (a6989586621679180196 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679180195 :: TyFun b (a ~> c) -> Type) (a6989586621679180196 :: b) = FlipSym2 a6989586621679180195 a6989586621679180196
type Apply (Tuple3Sym1 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679046761 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym1 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679046761 :: b) = Tuple3Sym2 a6989586621679046760 a6989586621679046761 :: TyFun c (a, b, c) -> Type
type Apply (Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type) (a6989586621680390415 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type) (a6989586621680390415 :: b) = Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type
type Apply (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) (a6989586621680390408 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) (a6989586621680390408 :: b) = FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type
type Apply (Foldr'Sym1 a6989586621680390400 :: TyFun b (t a ~> b) -> Type) (a6989586621680390401 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym1 a6989586621680390400 :: TyFun b (t a ~> b) -> Type) (a6989586621680390401 :: b) = Foldr'Sym2 a6989586621680390400 a6989586621680390401 :: TyFun (t a) b -> Type
type Apply (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) (a6989586621680390394 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) (a6989586621680390394 :: b) = FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type
type Apply (OnSym2 a6989586621679327018 a6989586621679327019 :: TyFun a (a ~> c) -> Type) (a6989586621679327020 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym2 a6989586621679327018 a6989586621679327019 :: TyFun a (a ~> c) -> Type) (a6989586621679327020 :: a) = OnSym3 a6989586621679327018 a6989586621679327019 a6989586621679327020
type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679046878 :: 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) (a6989586621679046878 :: a) = Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type
type Apply (MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741279 :: a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741279 :: a) = MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type
type Apply (MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741269 :: a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741269 :: a) = MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: TyFun (t b) (a, t c) -> Type
type Apply (Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679046810 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679046810 :: b) = Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type
type Apply (FoldlMSym1 a6989586621680390349 :: TyFun b (t a ~> m b) -> Type) (a6989586621680390350 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym1 a6989586621680390349 :: TyFun b (t a ~> m b) -> Type) (a6989586621680390350 :: b) = FoldlMSym2 a6989586621680390349 a6989586621680390350 :: TyFun (t a) (m b) -> Type
type Apply (FoldrMSym1 a6989586621680390367 :: TyFun b (t a ~> m b) -> Type) (a6989586621680390368 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym1 a6989586621680390367 :: TyFun b (t a ~> m b) -> Type) (a6989586621680390368 :: b) = FoldrMSym2 a6989586621680390367 a6989586621680390368 :: TyFun (t a) (m b) -> Type
type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679046969 :: 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) (a6989586621679046969 :: a) = Tuple6Sym1 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type
type Apply (Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679046879 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679046879 :: b) = Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type
type Apply (Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679046811 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679046811 :: c) = Tuple4Sym3 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: 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) (a6989586621679047084 :: 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) (a6989586621679047084 :: a) = Tuple7Sym1 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type
type Apply (Tuple6Sym1 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679046970 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym1 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679046970 :: b) = Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type
type Apply (Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679046880 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679046880 :: c) = Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type
type Apply (Tuple7Sym1 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679047085 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym1 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679047085 :: b) = Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type
type Apply (Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679046971 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679046971 :: c) = Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type
type Apply (Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679046881 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679046881 :: d) = Tuple5Sym4 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun e (a, b, c, d, e) -> Type
type Apply (Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679047086 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679047086 :: c) = Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type
type Apply (Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679046972 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679046972 :: d) = Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type
type Apply (Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679047087 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679047087 :: d) = Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type
type Apply (Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679046973 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679046973 :: e) = Tuple6Sym5 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun f (a, b, c, d, e, f) -> Type
type Apply (Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679047088 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679047088 :: e) = Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type
type Apply (Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679047089 :: f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679047089 :: f) = Tuple7Sym6 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun g (a, b, c, d, e, f, g) -> Type
type Apply (ConstSym0 :: TyFun a (Const a b) -> Type) (x :: a) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Apply (ConstSym0 :: TyFun a (Const a b) -> Type) (x :: a) = 'Const x :: Const a b
type Apply (Tuple3Sym2 a6989586621679046760 a6989586621679046761 :: TyFun k3 (k1, k2, k3) -> Type) (a6989586621679046762 :: k3) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym2 a6989586621679046760 a6989586621679046761 :: TyFun k3 (k1, k2, k3) -> Type) (a6989586621679046762 :: k3) = '(a6989586621679046760, a6989586621679046761, a6989586621679046762)
type Apply (Tuple4Sym3 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: TyFun k4 (k1, k2, k3, k4) -> Type) (a6989586621679046812 :: k4) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym3 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: TyFun k4 (k1, k2, k3, k4) -> Type) (a6989586621679046812 :: k4) = '(a6989586621679046809, a6989586621679046810, a6989586621679046811, a6989586621679046812)
type Apply (Tuple5Sym4 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun k5 (k1, k2, k3, k4, k5) -> Type) (a6989586621679046882 :: k5) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym4 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun k5 (k1, k2, k3, k4, k5) -> Type) (a6989586621679046882 :: k5) = '(a6989586621679046878, a6989586621679046879, a6989586621679046880, a6989586621679046881, a6989586621679046882)
type Apply (Tuple6Sym5 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun k6 (k1, k2, k3, k4, k5, k6) -> Type) (a6989586621679046974 :: k6) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym5 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun k6 (k1, k2, k3, k4, k5, k6) -> Type) (a6989586621679046974 :: k6) = '(a6989586621679046969, a6989586621679046970, a6989586621679046971, a6989586621679046972, a6989586621679046973, a6989586621679046974)
type Apply (Tuple7Sym6 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun k7 (k1, k2, k3, k4, k5, k6, k7) -> Type) (a6989586621679047090 :: k7) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym6 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun k7 (k1, k2, k3, k4, k5, k6, k7) -> Type) (a6989586621679047090 :: k7) = '(a6989586621679047084, a6989586621679047085, a6989586621679047086, a6989586621679047087, a6989586621679047088, a6989586621679047089, a6989586621679047090)
type Apply XorSym0 (a6989586621681120798 :: NonEmpty Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

type Apply UnwordsSym0 (a6989586621679815188 :: [Symbol]) = Unwords a6989586621679815188
type Apply (RunIdentitySym0 :: TyFun (Identity a) a -> Type) (a6989586621679047154 :: Identity a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Ord.Singletons

type Apply (GetDownSym0 :: TyFun (Down a) a -> Type) (a6989586621679248122 :: Down a) = GetDown a6989586621679248122
type Apply (GetFirstSym0 :: TyFun (First a) a -> Type) (a6989586621679687661 :: First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) (a6989586621679687699 :: WrappedMonoid m) = UnwrapMonoid a6989586621679687699
type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679687534 :: Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679687585 :: Sum a) = GetSum a6989586621679687585
type Apply (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) (a6989586621681120809 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621679207893 :: NonEmpty a) = Sconcat a6989586621679207893
type Apply (IsJustSym0 :: TyFun (Maybe a) Bool -> Type) (a6989586621679579807 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680390252 :: t Bool) = Or a6989586621680390252
type Apply (IsPrefixOfSym1 a6989586621681120403 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681120404 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IsPrefixOfSym1 a6989586621681120403 :: TyFun (NonEmpty a) Bool -> Type) (a6989586621681120404 :: NonEmpty a) = IsPrefixOf a6989586621681120403 a6989586621681120404
type Apply (FromMaybeSym1 a6989586621679579790 :: TyFun (Maybe a) a -> Type) (a6989586621679579791 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (FromMaybeSym1 a6989586621679579790 :: TyFun (Maybe a) a -> Type) (a6989586621679579791 :: Maybe a) = FromMaybe a6989586621679579790 a6989586621679579791
type Apply (IsInfixOfSym1 a6989586621679815396 :: TyFun [a] Bool -> Type) (a6989586621679815397 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsInfixOfSym1 a6989586621679815396 :: TyFun [a] Bool -> Type) (a6989586621679815397 :: [a]) = IsInfixOf a6989586621679815396 a6989586621679815397
type Apply (IsPrefixOfSym1 a6989586621679815410 :: TyFun [a] Bool -> Type) (a6989586621679815411 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsPrefixOfSym1 a6989586621679815410 :: TyFun [a] Bool -> Type) (a6989586621679815411 :: [a]) = IsPrefixOf a6989586621679815410 a6989586621679815411
type Apply (IsSuffixOfSym1 a6989586621679815403 :: TyFun [a] Bool -> Type) (a6989586621679815404 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IsSuffixOfSym1 a6989586621679815403 :: TyFun [a] Bool -> Type) (a6989586621679815404 :: [a]) = IsSuffixOf a6989586621679815403 a6989586621679815404
type Apply (Foldl1'Sym1 a6989586621679815658 :: TyFun [a] a -> Type) (a6989586621679815659 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Foldl1'Sym1 a6989586621679815658 :: TyFun [a] a -> Type) (a6989586621679815659 :: [a]) = Foldl1' a6989586621679815658 a6989586621679815659
type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679814589 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GenericLengthSym0 :: TyFun [a] k2 -> Type) (a6989586621679814589 :: [a]) = GenericLength a6989586621679814589 :: k2
type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680390443 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Apply (FoldSym0 :: TyFun (t m) m -> Type) (a6989586621680390383 :: t m) = Fold a6989586621680390383
type Apply (AsProxyTypeOfSym1 a6989586621680355908 :: TyFun (proxy a) a -> Type) (a6989586621680355909 :: proxy a) Source # 
Instance details

Defined in Data.Proxy.Singletons

type Apply (AsProxyTypeOfSym1 a6989586621680355908 :: TyFun (proxy a) a -> Type) (a6989586621680355909 :: proxy a) = AsProxyTypeOf a6989586621680355908 a6989586621680355909
type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680390435 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680390435 :: t a) = Length a6989586621680390435
type Apply (AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type) (a6989586621680390236 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type) (a6989586621680390236 :: t a) = All a6989586621680390235 a6989586621680390236
type Apply (AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type) (a6989586621680390245 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type) (a6989586621680390245 :: t a) = Any a6989586621680390244 a6989586621680390245
type Apply (ElemSym1 a6989586621680390439 :: TyFun (t a) Bool -> Type) (a6989586621680390440 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621680390439 :: TyFun (t a) Bool -> Type) (a6989586621680390440 :: t a) = Elem a6989586621680390439 a6989586621680390440
type Apply (NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type) (a6989586621680390187 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type) (a6989586621680390187 :: t a) = NotElem a6989586621680390186 a6989586621680390187
type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680390432 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680390432 :: t a) = Null a6989586621680390432
type Apply (Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type) (a6989586621680390426 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type) (a6989586621680390426 :: t a) = Foldl1 a6989586621680390425 a6989586621680390426
type Apply (Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type) (a6989586621680390421 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type) (a6989586621680390421 :: t a) = Foldr1 a6989586621680390420 a6989586621680390421
type Apply (MaximumBySym1 a6989586621680390215 :: TyFun (t a) a -> Type) (a6989586621680390216 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym1 a6989586621680390215 :: TyFun (t a) a -> Type) (a6989586621680390216 :: t a) = MaximumBy a6989586621680390215 a6989586621680390216
type Apply (MinimumBySym1 a6989586621680390195 :: TyFun (t a) a -> Type) (a6989586621680390196 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym1 a6989586621680390195 :: TyFun (t a) a -> Type) (a6989586621680390196 :: t a) = MinimumBy a6989586621680390195 a6989586621680390196
type Apply (Maybe_Sym2 a6989586621679577734 a6989586621679577735 :: TyFun (Maybe a) b -> Type) (a6989586621679577736 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym2 a6989586621679577734 a6989586621679577735 :: TyFun (Maybe a) b -> Type) (a6989586621679577736 :: Maybe a) = Maybe_ a6989586621679577734 a6989586621679577735 a6989586621679577736
type Apply (FoldMapSym1 a6989586621680390387 :: TyFun (t a) m -> Type) (a6989586621680390388 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym1 a6989586621680390387 :: TyFun (t a) m -> Type) (a6989586621680390388 :: t a) = FoldMap a6989586621680390387 a6989586621680390388
type Apply (FoldMapDefaultSym1 a6989586621680741235 :: TyFun (t a) m -> Type) (a6989586621680741236 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FoldMapDefaultSym1 a6989586621680741235 :: TyFun (t a) m -> Type) (a6989586621680741236 :: t a) = FoldMapDefault a6989586621680741235 a6989586621680741236
type Apply (Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type) (a6989586621680390416 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type) (a6989586621680390416 :: t a) = Foldl' a6989586621680390414 a6989586621680390415 a6989586621680390416
type Apply (FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type) (a6989586621680390409 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type) (a6989586621680390409 :: t a) = Foldl a6989586621680390407 a6989586621680390408 a6989586621680390409
type Apply (Foldr'Sym2 a6989586621680390400 a6989586621680390401 :: TyFun (t a) b -> Type) (a6989586621680390402 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym2 a6989586621680390400 a6989586621680390401 :: TyFun (t a) b -> Type) (a6989586621680390402 :: t a) = Foldr' a6989586621680390400 a6989586621680390401 a6989586621680390402
type Apply (FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type) (a6989586621680390395 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type) (a6989586621680390395 :: t a) = Foldr a6989586621680390393 a6989586621680390394 a6989586621680390395
type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680296693 :: First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680296716 :: Last a) = GetLast a6989586621680296716
type Apply (TransposeSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120316 :: NonEmpty (NonEmpty a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

type Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120695 :: NonEmpty a) = ToList a6989586621681120695
type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621680296690 :: Maybe a) Source # 
Instance details

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679815813 :: [a]) = Tail a6989586621679815813
type Apply (GroupBy1Sym1 a6989586621681120430 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120431 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBy1Sym1 a6989586621681120430 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120431 :: NonEmpty a) = GroupBy1 a6989586621681120430 a6989586621681120431
type Apply ((<|@#@$$) a6989586621681120723 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120724 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((<|@#@$$) a6989586621681120723 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120724 :: NonEmpty a) = a6989586621681120723 <| a6989586621681120724
type Apply (ConsSym1 a6989586621681120716 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120717 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ConsSym1 a6989586621681120716 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120717 :: NonEmpty a) = Cons a6989586621681120716 a6989586621681120717
type Apply (IntersperseSym1 a6989586621681120607 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120608 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (IntersperseSym1 a6989586621681120607 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120608 :: NonEmpty a) = Intersperse a6989586621681120607 a6989586621681120608
type Apply (NubBySym1 a6989586621681120321 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120322 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym1 a6989586621681120321 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120322 :: NonEmpty a) = NubBy a6989586621681120321 a6989586621681120322
type Apply (Scanl1Sym1 a6989586621681120626 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120627 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym1 a6989586621681120626 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120627 :: NonEmpty a) = Scanl1 a6989586621681120626 a6989586621681120627
type Apply (Scanr1Sym1 a6989586621681120618 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120619 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym1 a6989586621681120618 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120619 :: NonEmpty a) = Scanr1 a6989586621681120618 a6989586621681120619
type Apply (SortBySym1 a6989586621681120308 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120309 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym1 a6989586621681120308 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120309 :: NonEmpty a) = SortBy a6989586621681120308 a6989586621681120309
type Apply (DropSym1 a6989586621681120585 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120586 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropSym1 a6989586621681120585 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120586 :: NonEmpty a) = Drop a6989586621681120585 a6989586621681120586
type Apply (DropWhileSym1 a6989586621681120558 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120559 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym1 a6989586621681120558 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120559 :: NonEmpty a) = DropWhile a6989586621681120558 a6989586621681120559
type Apply (FilterSym1 a6989586621681120531 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120532 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym1 a6989586621681120531 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120532 :: NonEmpty a) = Filter a6989586621681120531 a6989586621681120532
type Apply (TakeSym1 a6989586621681120594 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120595 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeSym1 a6989586621681120594 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120595 :: NonEmpty a) = Take a6989586621681120594 a6989586621681120595
type Apply (TakeWhileSym1 a6989586621681120567 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120568 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym1 a6989586621681120567 :: TyFun (NonEmpty a) [a] -> Type) (a6989586621681120568 :: NonEmpty a) = TakeWhile a6989586621681120567 a6989586621681120568
type Apply ((:$$:@#@$$) a6989586621680205232 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621680205233 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply ((:$$:@#@$$) a6989586621680205232 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621680205233 :: ErrorMessage' s) = a6989586621680205232 ':$$: a6989586621680205233
type Apply ((:<>:@#@$$) a6989586621680205229 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) (a6989586621680205230 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

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

Defined in Data.Either.Singletons

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

Defined in Data.Either.Singletons

type Apply (RightsSym0 :: TyFun [Either a b] [b] -> Type) (a6989586621679337122 :: [Either a b]) = Rights a6989586621679337122
type Apply (IntercalateSym1 a6989586621679815772 :: TyFun [[a]] [a] -> Type) (a6989586621679815773 :: [[a]]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntercalateSym1 a6989586621679815772 :: TyFun [[a]] [a] -> Type) (a6989586621679815773 :: [[a]]) = Intercalate a6989586621679815772 a6989586621679815773
type Apply (InsertSym1 a6989586621681120660 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681120661 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (InsertSym1 a6989586621681120660 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621681120661 :: [a]) = Insert a6989586621681120660 a6989586621681120661
type Apply ((:|@#@$$) a6989586621679046311 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679046312 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:|@#@$$) a6989586621679046311 :: TyFun [a] (NonEmpty a) -> Type) (a6989586621679046312 :: [a]) = a6989586621679046311 ':| a6989586621679046312
type Apply (ElemIndexSym1 a6989586621679815037 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679815038 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndexSym1 a6989586621679815037 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679815038 :: [a]) = ElemIndex a6989586621679815037 a6989586621679815038
type Apply (FindIndexSym1 a6989586621679815019 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679815020 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym1 a6989586621679815019 :: TyFun [a] (Maybe Natural) -> Type) (a6989586621679815020 :: [a]) = FindIndex a6989586621679815019 a6989586621679815020
type Apply (StripPrefixSym1 a6989586621679966032 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679966033 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (StripPrefixSym1 a6989586621679966032 :: TyFun [a] (Maybe [a]) -> Type) (a6989586621679966033 :: [a]) = StripPrefix a6989586621679966032 a6989586621679966033
type Apply (GroupBySym1 a6989586621681120482 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120483 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym1 a6989586621681120482 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120483 :: [a]) = GroupBy a6989586621681120482 a6989586621681120483
type Apply (ElemIndicesSym1 a6989586621679815028 :: TyFun [a] [Natural] -> Type) (a6989586621679815029 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ElemIndicesSym1 a6989586621679815028 :: TyFun [a] [Natural] -> Type) (a6989586621679815029 :: [a]) = ElemIndices a6989586621679815028 a6989586621679815029
type Apply (FindIndicesSym1 a6989586621679814996 :: TyFun [a] [Natural] -> Type) (a6989586621679814997 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndicesSym1 a6989586621679814996 :: TyFun [a] [Natural] -> Type) (a6989586621679814997 :: [a]) = FindIndices a6989586621679814996 a6989586621679814997
type Apply (GroupBySym1 a6989586621679814759 :: TyFun [a] [[a]] -> Type) (a6989586621679814760 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GroupBySym1 a6989586621679814759 :: TyFun [a] [[a]] -> Type) (a6989586621679814760 :: [a]) = GroupBy a6989586621679814759 a6989586621679814760
type Apply (DeleteSym1 a6989586621679815182 :: TyFun [a] [a] -> Type) (a6989586621679815183 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteSym1 a6989586621679815182 :: TyFun [a] [a] -> Type) (a6989586621679815183 :: [a]) = Delete a6989586621679815182 a6989586621679815183
type Apply (DropSym1 a6989586621679814823 :: TyFun [a] [a] -> Type) (a6989586621679814824 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym1 a6989586621679814823 :: TyFun [a] [a] -> Type) (a6989586621679814824 :: [a]) = Drop a6989586621679814823 a6989586621679814824
type Apply (DropWhileEndSym1 a6989586621679814921 :: TyFun [a] [a] -> Type) (a6989586621679814922 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym1 a6989586621679814921 :: TyFun [a] [a] -> Type) (a6989586621679814922 :: [a]) = DropWhileEnd a6989586621679814921 a6989586621679814922
type Apply (DropWhileSym1 a6989586621679814938 :: TyFun [a] [a] -> Type) (a6989586621679814939 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym1 a6989586621679814938 :: TyFun [a] [a] -> Type) (a6989586621679814939 :: [a]) = DropWhile a6989586621679814938 a6989586621679814939
type Apply (FilterSym1 a6989586621679815053 :: TyFun [a] [a] -> Type) (a6989586621679815054 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym1 a6989586621679815053 :: TyFun [a] [a] -> Type) (a6989586621679815054 :: [a]) = Filter a6989586621679815053 a6989586621679815054
type Apply (InsertSym1 a6989586621679814791 :: TyFun [a] [a] -> Type) (a6989586621679814792 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertSym1 a6989586621679814791 :: TyFun [a] [a] -> Type) (a6989586621679814792 :: [a]) = Insert a6989586621679814791 a6989586621679814792
type Apply (IntersectSym1 a6989586621679814989 :: TyFun [a] [a] -> Type) (a6989586621679814990 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectSym1 a6989586621679814989 :: TyFun [a] [a] -> Type) (a6989586621679814990 :: [a]) = Intersect a6989586621679814989 a6989586621679814990
type Apply (IntersperseSym1 a6989586621679815779 :: TyFun [a] [a] -> Type) (a6989586621679815780 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersperseSym1 a6989586621679815779 :: TyFun [a] [a] -> Type) (a6989586621679815780 :: [a]) = Intersperse a6989586621679815779 a6989586621679815780
type Apply (NubBySym1 a6989586621679814626 :: TyFun [a] [a] -> Type) (a6989586621679814627 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NubBySym1 a6989586621679814626 :: TyFun [a] [a] -> Type) (a6989586621679814627 :: [a]) = NubBy a6989586621679814626 a6989586621679814627
type Apply (Scanl1Sym1 a6989586621679815582 :: TyFun [a] [a] -> Type) (a6989586621679815583 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym1 a6989586621679815582 :: TyFun [a] [a] -> Type) (a6989586621679815583 :: [a]) = Scanl1 a6989586621679815582 a6989586621679815583
type Apply (Scanr1Sym1 a6989586621679815544 :: TyFun [a] [a] -> Type) (a6989586621679815545 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym1 a6989586621679815544 :: TyFun [a] [a] -> Type) (a6989586621679815545 :: [a]) = Scanr1 a6989586621679815544 a6989586621679815545
type Apply (SortBySym1 a6989586621679815130 :: TyFun [a] [a] -> Type) (a6989586621679815131 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SortBySym1 a6989586621679815130 :: TyFun [a] [a] -> Type) (a6989586621679815131 :: [a]) = SortBy a6989586621679815130 a6989586621679815131
type Apply (TakeSym1 a6989586621679814836 :: TyFun [a] [a] -> Type) (a6989586621679814837 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym1 a6989586621679814836 :: TyFun [a] [a] -> Type) (a6989586621679814837 :: [a]) = Take a6989586621679814836 a6989586621679814837
type Apply (TakeWhileSym1 a6989586621679814953 :: TyFun [a] [a] -> Type) (a6989586621679814954 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym1 a6989586621679814953 :: TyFun [a] [a] -> Type) (a6989586621679814954 :: [a]) = TakeWhile a6989586621679814953 a6989586621679814954
type Apply (UnionSym1 a6989586621679814598 :: TyFun [a] [a] -> Type) (a6989586621679814599 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionSym1 a6989586621679814598 :: TyFun [a] [a] -> Type) (a6989586621679814599 :: [a]) = Union a6989586621679814598 a6989586621679814599
type Apply ((\\@#@$$) a6989586621679815171 :: TyFun [a] [a] -> Type) (a6989586621679815172 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((\\@#@$$) a6989586621679815171 :: TyFun [a] [a] -> Type) (a6989586621679815172 :: [a]) = a6989586621679815171 \\ a6989586621679815172
type Apply ((:@#@$$) a6989586621679046238 :: TyFun [a] [a] -> Type) (a6989586621679046239 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$$) a6989586621679046238 :: TyFun [a] [a] -> Type) (a6989586621679046239 :: [a]) = a6989586621679046238 ': a6989586621679046239
type Apply ((++@#@$$) a6989586621679180230 :: TyFun [a] [a] -> Type) (a6989586621679180231 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$$) a6989586621679180230 :: TyFun [a] [a] -> Type) (a6989586621679180231 :: [a]) = a6989586621679180230 ++ a6989586621679180231
type Apply (UnlessSym1 a6989586621681205232 :: TyFun (f ()) (f ()) -> Type) (a6989586621681205233 :: f ()) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (UnlessSym1 a6989586621681205232 :: TyFun (f ()) (f ()) -> Type) (a6989586621681205233 :: f ()) = Unless a6989586621681205232 a6989586621681205233
type Apply (WhenSym1 a6989586621679348427 :: TyFun (f ()) (f ()) -> Type) (a6989586621679348428 :: f ()) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (WhenSym1 a6989586621679348427 :: TyFun (f ()) (f ()) -> Type) (a6989586621679348428 :: f ()) = When a6989586621679348427 a6989586621679348428
type Apply (OptionalSym0 :: TyFun (f a) (f (Maybe a)) -> Type) (a6989586621681182611 :: f a) Source # 
Instance details

Defined in Control.Applicative.Singletons

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

Defined in Data.Functor.Singletons

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

Defined in Control.Monad.Singletons.Internal

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (a6989586621680390429 :: t a) = ToList a6989586621680390429
type Apply (GroupAllWith1Sym1 a6989586621681120414 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120415 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym1 a6989586621681120414 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120415 :: NonEmpty a) = GroupAllWith1 a6989586621681120414 a6989586621681120415
type Apply (GroupWith1Sym1 a6989586621681120423 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120424 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym1 a6989586621681120423 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) (a6989586621681120424 :: NonEmpty a) = GroupWith1 a6989586621681120423 a6989586621681120424
type Apply (SortWithSym1 a6989586621681120299 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120300 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym1 a6989586621681120299 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) (a6989586621681120300 :: NonEmpty a) = SortWith a6989586621681120299 a6989586621681120300
type Apply (MapSym1 a6989586621681120679 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681120680 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym1 a6989586621681120679 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) (a6989586621681120680 :: NonEmpty a) = Map a6989586621681120679 a6989586621681120680
type Apply (ZipSym1 a6989586621681120375 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681120376 :: NonEmpty b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym1 a6989586621681120375 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) (a6989586621681120376 :: NonEmpty b) = Zip a6989586621681120375 a6989586621681120376
type Apply (LookupSym1 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679814745 :: [(a, b)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym1 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679814745 :: [(a, b)]) = Lookup a6989586621679814744 a6989586621679814745
type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679549513 :: [Char]) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679549513 :: [Char]) = Fail a6989586621679549513 :: m a
type Apply (GroupAllWithSym1 a6989586621681120464 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120465 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym1 a6989586621681120464 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120465 :: [a]) = GroupAllWith a6989586621681120464 a6989586621681120465
type Apply (GroupWithSym1 a6989586621681120473 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120474 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym1 a6989586621681120473 :: TyFun [a] [NonEmpty a] -> Type) (a6989586621681120474 :: [a]) = GroupWith a6989586621681120473 a6989586621681120474
type Apply (DeleteBySym2 a6989586621679815152 a6989586621679815153 :: TyFun [a] [a] -> Type) (a6989586621679815154 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym2 a6989586621679815152 a6989586621679815153 :: TyFun [a] [a] -> Type) (a6989586621679815154 :: [a]) = DeleteBy a6989586621679815152 a6989586621679815153 a6989586621679815154
type Apply (DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143 :: TyFun [a] [a] -> Type) (a6989586621679815144 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143 :: TyFun [a] [a] -> Type) (a6989586621679815144 :: [a]) = DeleteFirstsBy a6989586621679815142 a6989586621679815143 a6989586621679815144
type Apply (InsertBySym2 a6989586621679815110 a6989586621679815111 :: TyFun [a] [a] -> Type) (a6989586621679815112 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym2 a6989586621679815110 a6989586621679815111 :: TyFun [a] [a] -> Type) (a6989586621679815112 :: [a]) = InsertBy a6989586621679815110 a6989586621679815111 a6989586621679815112
type Apply (IntersectBySym2 a6989586621679814967 a6989586621679814968 :: TyFun [a] [a] -> Type) (a6989586621679814969 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym2 a6989586621679814967 a6989586621679814968 :: TyFun [a] [a] -> Type) (a6989586621679814969 :: [a]) = IntersectBy a6989586621679814967 a6989586621679814968 a6989586621679814969
type Apply (UnionBySym2 a6989586621679814606 a6989586621679814607 :: TyFun [a] [a] -> Type) (a6989586621679814608 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym2 a6989586621679814606 a6989586621679814607 :: TyFun [a] [a] -> Type) (a6989586621679814608 :: [a]) = UnionBy a6989586621679814606 a6989586621679814607 a6989586621679814608
type Apply (MapMaybeSym1 a6989586621679579760 :: TyFun [a] [b] -> Type) (a6989586621679579761 :: [a]) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MapMaybeSym1 a6989586621679579760 :: TyFun [a] [b] -> Type) (a6989586621679579761 :: [a]) = MapMaybe a6989586621679579760 a6989586621679579761
type Apply (MapSym1 a6989586621679180239 :: TyFun [a] [b] -> Type) (a6989586621679180240 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym1 a6989586621679180239 :: TyFun [a] [b] -> Type) (a6989586621679180240 :: [a]) = Map a6989586621679180239 a6989586621679180240
type Apply (FilterMSym1 a6989586621681205365 :: TyFun [a] (m [a]) -> Type) (a6989586621681205366 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (FilterMSym1 a6989586621681205365 :: TyFun [a] (m [a]) -> Type) (a6989586621681205366 :: [a]) = FilterM a6989586621681205365 a6989586621681205366
type Apply (ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type) (a6989586621679815372 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type) (a6989586621679815372 :: [b]) = Zip a6989586621679815371 a6989586621679815372
type Apply (ReplicateM_Sym1 a6989586621681205242 :: TyFun (m a) (m ()) -> Type) (a6989586621681205243 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ReplicateM_Sym1 a6989586621681205242 :: TyFun (m a) (m ()) -> Type) (a6989586621681205243 :: m a) = ReplicateM_ a6989586621681205242 a6989586621681205243
type Apply (ReplicateMSym1 a6989586621681205260 :: TyFun (m a) (m [a]) -> Type) (a6989586621681205261 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ReplicateMSym1 a6989586621681205260 :: TyFun (m a) (m [a]) -> Type) (a6989586621681205261 :: m a) = ReplicateM a6989586621681205260 a6989586621681205261
type Apply (MfilterSym1 a6989586621681205203 :: TyFun (m a) (m a) -> Type) (a6989586621681205204 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MfilterSym1 a6989586621681205203 :: TyFun (m a) (m a) -> Type) (a6989586621681205204 :: m a) = Mfilter a6989586621681205203 a6989586621681205204
type Apply (FindSym1 a6989586621680390168 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680390169 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym1 a6989586621680390168 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680390169 :: t a) = Find a6989586621680390168 a6989586621680390169
type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621680390303 :: t (f a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621680390303 :: t (f a)) = SequenceA_ a6989586621680390303
type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680733990 :: t (f a)) Source # 
Instance details

Defined in Data.Traversable.Singletons

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

Defined in Data.Foldable.Singletons

type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621680390297 :: t (m a)) = Sequence_ a6989586621680390297
type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680733998 :: t (m a)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680733998 :: t (m a)) = Sequence a6989586621680733998
type Apply (ScanlSym2 a6989586621681120649 a6989586621681120650 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120651 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym2 a6989586621681120649 a6989586621681120650 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120651 :: [a]) = Scanl a6989586621681120649 a6989586621681120650 a6989586621681120651
type Apply (ScanrSym2 a6989586621681120637 a6989586621681120638 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120639 :: [a]) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym2 a6989586621681120637 a6989586621681120638 :: TyFun [a] (NonEmpty b) -> Type) (a6989586621681120639 :: [a]) = Scanr a6989586621681120637 a6989586621681120638 a6989586621681120639
type Apply (ScanlSym2 a6989586621679815591 a6989586621679815592 :: TyFun [a] [b] -> Type) (a6989586621679815593 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym2 a6989586621679815591 a6989586621679815592 :: TyFun [a] [b] -> Type) (a6989586621679815593 :: [a]) = Scanl a6989586621679815591 a6989586621679815592 a6989586621679815593
type Apply (ScanrSym2 a6989586621679815564 a6989586621679815565 :: TyFun [a] [b] -> Type) (a6989586621679815566 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym2 a6989586621679815564 a6989586621679815565 :: TyFun [a] [b] -> Type) (a6989586621679815566 :: [a]) = Scanr a6989586621679815564 a6989586621679815565 a6989586621679815566
type Apply ((<**>@#@$$) a6989586621679348472 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679348473 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<**>@#@$$) a6989586621679348472 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679348473 :: f (a ~> b)) = a6989586621679348472 <**> a6989586621679348473
type Apply ((<|>@#@$$) a6989586621679348633 :: TyFun (f a) (f a) -> Type) (a6989586621679348634 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<|>@#@$$) a6989586621679348633 :: TyFun (f a) (f a) -> Type) (a6989586621679348634 :: f a) = a6989586621679348633 <|> a6989586621679348634
type Apply ((<*>@#@$$) a6989586621679348512 :: TyFun (f a) (f b) -> Type) (a6989586621679348513 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$$) a6989586621679348512 :: TyFun (f a) (f b) -> Type) (a6989586621679348513 :: f a) = a6989586621679348512 <*> a6989586621679348513
type Apply (FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type) (a6989586621679348485 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type) (a6989586621679348485 :: f a) = Fmap a6989586621679348484 a6989586621679348485
type Apply (LiftASym1 a6989586621679348461 :: TyFun (f a) (f b) -> Type) (a6989586621679348462 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftASym1 a6989586621679348461 :: TyFun (f a) (f b) -> Type) (a6989586621679348462 :: f a) = LiftA a6989586621679348461 a6989586621679348462
type Apply ((<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type) (a6989586621679532920 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type) (a6989586621679532920 :: f a) = a6989586621679532919 <$> a6989586621679532920
type Apply ((<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type) (a6989586621679348490 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type) (a6989586621679348490 :: f b) = a6989586621679348489 <$ a6989586621679348490
type Apply (MplusSym1 a6989586621679348639 :: TyFun (m a) (m a) -> Type) (a6989586621679348640 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (MplusSym1 a6989586621679348639 :: TyFun (m a) (m a) -> Type) (a6989586621679348640 :: m a) = Mplus a6989586621679348639 a6989586621679348640
type Apply ((<$!>@#@$$) a6989586621681205219 :: TyFun (m a) (m b) -> Type) (a6989586621681205220 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<$!>@#@$$) a6989586621681205219 :: TyFun (m a) (m b) -> Type) (a6989586621681205220 :: m a) = a6989586621681205219 <$!> a6989586621681205220
type Apply ((=<<@#@$$) a6989586621679348437 :: TyFun (m a) (m b) -> Type) (a6989586621679348438 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$$) a6989586621679348437 :: TyFun (m a) (m b) -> Type) (a6989586621679348438 :: m a) = a6989586621679348437 =<< a6989586621679348438
type Apply (ApSym1 a6989586621679348287 :: TyFun (m a) (m b) -> Type) (a6989586621679348288 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ApSym1 a6989586621679348287 :: TyFun (m a) (m b) -> Type) (a6989586621679348288 :: m a) = Ap a6989586621679348287 a6989586621679348288
type Apply (LiftMSym1 a6989586621679348416 :: TyFun (m a1) (m r) -> Type) (a6989586621679348417 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftMSym1 a6989586621679348416 :: TyFun (m a1) (m r) -> Type) (a6989586621679348417 :: m a1) = LiftM a6989586621679348416 a6989586621679348417
type Apply (MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type) (a6989586621681083532 :: m b) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type) (a6989586621681083532 :: m b) = Mzip a6989586621681083531 a6989586621681083532
type Apply (ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type) (a6989586621680390264 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type) (a6989586621680390264 :: t a) = ConcatMap a6989586621680390263 a6989586621680390264
type Apply (FmapDefaultSym1 a6989586621680741254 :: TyFun (t a) (t b) -> Type) (a6989586621680741255 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FmapDefaultSym1 a6989586621680741254 :: TyFun (t a) (t b) -> Type) (a6989586621680741255 :: t a) = FmapDefault a6989586621680741254 a6989586621680741255
type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621680390291 :: t (f a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621680390291 :: t (f a)) = Asum a6989586621680390291
type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621680390285 :: t (m a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621680390285 :: t (m a)) = Msum a6989586621680390285
type Apply (ZipWithSym2 a6989586621681120364 a6989586621681120365 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681120366 :: NonEmpty b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym2 a6989586621681120364 a6989586621681120365 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) (a6989586621681120366 :: NonEmpty b) = ZipWith a6989586621681120364 a6989586621681120365 a6989586621681120366
type Apply (MapAndUnzipMSym1 a6989586621681205324 :: TyFun [a] (m ([b], [c])) -> Type) (a6989586621681205325 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MapAndUnzipMSym1 a6989586621681205324 :: TyFun [a] (m ([b], [c])) -> Type) (a6989586621681205325 :: [a]) = MapAndUnzipM a6989586621681205324 a6989586621681205325
type Apply (ZipWithSym2 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) (a6989586621679815349 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym2 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) (a6989586621679815349 :: [b]) = ZipWith a6989586621679815347 a6989586621679815348 a6989586621679815349
type Apply (Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679815361 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679815361 :: [c]) = Zip3 a6989586621679815359 a6989586621679815360 a6989586621679815361
type Apply ((<*@#@$$) a6989586621679348529 :: TyFun (f b) (f a) -> Type) (a6989586621679348530 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$$) a6989586621679348529 :: TyFun (f b) (f a) -> Type) (a6989586621679348530 :: f b) = a6989586621679348529 <* a6989586621679348530
type Apply ((*>@#@$$) a6989586621679348524 :: TyFun (f b) (f b) -> Type) (a6989586621679348525 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$$) a6989586621679348524 :: TyFun (f b) (f b) -> Type) (a6989586621679348525 :: f b) = a6989586621679348524 *> a6989586621679348525
type Apply ((>>@#@$$) a6989586621679348597 :: TyFun (m b) (m b) -> Type) (a6989586621679348598 :: m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$$) a6989586621679348597 :: TyFun (m b) (m b) -> Type) (a6989586621679348598 :: m b) = a6989586621679348597 >> a6989586621679348598
type Apply (Traverse_Sym1 a6989586621680390341 :: TyFun (t a) (f ()) -> Type) (a6989586621680390342 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym1 a6989586621680390341 :: TyFun (t a) (f ()) -> Type) (a6989586621680390342 :: t a) = Traverse_ a6989586621680390341 a6989586621680390342
type Apply (TraverseSym1 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680733987 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym1 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680733987 :: t a) = Traverse a6989586621680733986 a6989586621680733987
type Apply (MapM_Sym1 a6989586621680390321 :: TyFun (t a) (m ()) -> Type) (a6989586621680390322 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym1 a6989586621680390321 :: TyFun (t a) (m ()) -> Type) (a6989586621680390322 :: t a) = MapM_ a6989586621680390321 a6989586621680390322
type Apply (MapMSym1 a6989586621680733994 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680733995 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym1 a6989586621680733994 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680733995 :: t a) = MapM a6989586621680733994 a6989586621680733995
type Apply (ZipWithM_Sym2 a6989586621681205305 a6989586621681205306 :: TyFun [b] (m ()) -> Type) (a6989586621681205307 :: [b]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithM_Sym2 a6989586621681205305 a6989586621681205306 :: TyFun [b] (m ()) -> Type) (a6989586621681205307 :: [b]) = ZipWithM_ a6989586621681205305 a6989586621681205306 a6989586621681205307
type Apply (ZipWithMSym2 a6989586621681205315 a6989586621681205316 :: TyFun [b] (m [c]) -> Type) (a6989586621681205317 :: [b]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithMSym2 a6989586621681205315 a6989586621681205316 :: TyFun [b] (m [c]) -> Type) (a6989586621681205317 :: [b]) = ZipWithM a6989586621681205315 a6989586621681205316 a6989586621681205317
type Apply (LiftA2Sym2 a6989586621679348518 a6989586621679348519 :: TyFun (f b) (f c) -> Type) (a6989586621679348520 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym2 a6989586621679348518 a6989586621679348519 :: TyFun (f b) (f c) -> Type) (a6989586621679348520 :: f b) = LiftA2 a6989586621679348518 a6989586621679348519 a6989586621679348520
type Apply (LiftM2Sym2 a6989586621679348399 a6989586621679348400 :: TyFun (m a2) (m r) -> Type) (a6989586621679348401 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM2Sym2 a6989586621679348399 a6989586621679348400 :: TyFun (m a2) (m r) -> Type) (a6989586621679348401 :: m a2) = LiftM2 a6989586621679348399 a6989586621679348400 a6989586621679348401
type Apply (MzipWithSym2 a6989586621681083537 a6989586621681083538 :: TyFun (m b) (m c) -> Type) (a6989586621681083539 :: m b) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym2 a6989586621681083537 a6989586621681083538 :: TyFun (m b) (m c) -> Type) (a6989586621681083539 :: m b) = MzipWith a6989586621681083537 a6989586621681083538 a6989586621681083539
type Apply (FoldlMSym2 a6989586621680390349 a6989586621680390350 :: TyFun (t a) (m b) -> Type) (a6989586621680390351 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym2 a6989586621680390349 a6989586621680390350 :: TyFun (t a) (m b) -> Type) (a6989586621680390351 :: t a) = FoldlM a6989586621680390349 a6989586621680390350 a6989586621680390351
type Apply (FoldrMSym2 a6989586621680390367 a6989586621680390368 :: TyFun (t a) (m b) -> Type) (a6989586621680390369 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym2 a6989586621680390367 a6989586621680390368 :: TyFun (t a) (m b) -> Type) (a6989586621680390369 :: t a) = FoldrM a6989586621680390367 a6989586621680390368 a6989586621680390369
type Apply (ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) (a6989586621679815335 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) (a6989586621679815335 :: [c]) = ZipWith3 a6989586621679815332 a6989586621679815333 a6989586621679815334 a6989586621679815335
type Apply (Zip4Sym3 a6989586621679966021 a6989586621679966022 a6989586621679966023 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621679966024 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym3 a6989586621679966021 a6989586621679966022 a6989586621679966023 :: TyFun [d] [(a, b, c, d)] -> Type) (a6989586621679966024 :: [d]) = Zip4 a6989586621679966021 a6989586621679966022 a6989586621679966023 a6989586621679966024
type Apply (LiftA3Sym3 a6989586621679348450 a6989586621679348451 a6989586621679348452 :: TyFun (f c) (f d) -> Type) (a6989586621679348453 :: f c) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym3 a6989586621679348450 a6989586621679348451 a6989586621679348452 :: TyFun (f c) (f d) -> Type) (a6989586621679348453 :: f c) = LiftA3 a6989586621679348450 a6989586621679348451 a6989586621679348452 a6989586621679348453
type Apply (LiftM3Sym3 a6989586621679348375 a6989586621679348376 a6989586621679348377 :: TyFun (m a3) (m r) -> Type) (a6989586621679348378 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym3 a6989586621679348375 a6989586621679348376 a6989586621679348377 :: TyFun (m a3) (m r) -> Type) (a6989586621679348378 :: m a3) = LiftM3 a6989586621679348375 a6989586621679348376 a6989586621679348377 a6989586621679348378
type Apply (ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 :: TyFun [d] [e] -> Type) (a6989586621679965905 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 :: TyFun [d] [e] -> Type) (a6989586621679965905 :: [d]) = ZipWith4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 a6989586621679965905
type Apply (Zip5Sym4 a6989586621679965998 a6989586621679965999 a6989586621679966000 a6989586621679966001 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621679966002 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym4 a6989586621679965998 a6989586621679965999 a6989586621679966000 a6989586621679966001 :: TyFun [e] [(a, b, c, d, e)] -> Type) (a6989586621679966002 :: [e]) = Zip5 a6989586621679965998 a6989586621679965999 a6989586621679966000 a6989586621679966001 a6989586621679966002
type Apply (LiftM4Sym4 a6989586621679348344 a6989586621679348345 a6989586621679348346 a6989586621679348347 :: TyFun (m a4) (m r) -> Type) (a6989586621679348348 :: m a4) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym4 a6989586621679348344 a6989586621679348345 a6989586621679348346 a6989586621679348347 :: TyFun (m a4) (m r) -> Type) (a6989586621679348348 :: m a4) = LiftM4 a6989586621679348344 a6989586621679348345 a6989586621679348346 a6989586621679348347 a6989586621679348348
type Apply (ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 :: TyFun [e] [f] -> Type) (a6989586621679965883 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 :: TyFun [e] [f] -> Type) (a6989586621679965883 :: [e]) = ZipWith5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 a6989586621679965883
type Apply (Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679965975 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) (a6989586621679965975 :: [f]) = Zip6 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 a6989586621679965975
type Apply (LiftM5Sym5 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 a6989586621679348310 :: TyFun (m a5) (m r) -> Type) (a6989586621679348311 :: m a5) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym5 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 a6989586621679348310 :: TyFun (m a5) (m r) -> Type) (a6989586621679348311 :: m a5) = LiftM5 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 a6989586621679348310 a6989586621679348311
type Apply (ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 :: TyFun [f] [g] -> Type) (a6989586621679965857 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 :: TyFun [f] [g] -> Type) (a6989586621679965857 :: [f]) = ZipWith6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 a6989586621679965857
type Apply (Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679965943 :: [g]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) (a6989586621679965943 :: [g]) = Zip7 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 a6989586621679965943
type Apply (ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 :: TyFun [g] [h] -> Type) (a6989586621679965827 :: [g]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 :: TyFun [g] [h] -> Type) (a6989586621679965827 :: [g]) = ZipWith7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 a6989586621679965827
type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621681120384 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.Singletons.Base.TypeError

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

Defined in Data.Singletons.Base.TypeError

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in GHC.Base.Singletons

type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679180230 :: [a]) = (++@#@$$) a6989586621679180230
type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208723 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208723 :: [a]) = ShowListSym1 a6989586621680208723
type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681120338 :: NonEmpty (a, b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) (a6989586621681120338 :: NonEmpty (a, b)) = Unzip a6989586621681120338
type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621681120375 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621681120375 :: NonEmpty a) = ZipSym1 a6989586621681120375 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type
type Apply (BreakSym1 a6989586621681120540 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120541 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym1 a6989586621681120540 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120541 :: NonEmpty a) = Break a6989586621681120540 a6989586621681120541
type Apply (PartitionSym1 a6989586621681120522 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120523 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym1 a6989586621681120522 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120523 :: NonEmpty a) = Partition a6989586621681120522 a6989586621681120523
type Apply (SpanSym1 a6989586621681120549 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120550 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym1 a6989586621681120549 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120550 :: NonEmpty a) = Span a6989586621681120549 a6989586621681120550
type Apply (SplitAtSym1 a6989586621681120576 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120577 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SplitAtSym1 a6989586621681120576 :: TyFun (NonEmpty a) ([a], [a]) -> Type) (a6989586621681120577 :: NonEmpty a) = SplitAt a6989586621681120576 a6989586621681120577
type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679815313 :: [(a, b)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679815313 :: [(a, b)]) = Unzip a6989586621679815313
type Apply (DeleteFirstsBySym1 a6989586621679815142 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679815143 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym1 a6989586621679815142 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679815143 :: [a]) = DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143
type Apply (IntersectBySym1 a6989586621679814967 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814968 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym1 a6989586621679814967 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814968 :: [a]) = IntersectBySym2 a6989586621679814967 a6989586621679814968
type Apply (UnionBySym1 a6989586621679814606 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814607 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym1 a6989586621679814606 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814607 :: [a]) = UnionBySym2 a6989586621679814606 a6989586621679814607
type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679815371 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679815371 :: [a]) = ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type
type Apply (ShowListWithSym1 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208689 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym1 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208689 :: [a]) = ShowListWithSym2 a6989586621680208688 a6989586621680208689
type Apply (BreakSym1 a6989586621679814849 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814850 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym1 a6989586621679814849 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814850 :: [a]) = Break a6989586621679814849 a6989586621679814850
type Apply (PartitionSym1 a6989586621679814737 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814738 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (PartitionSym1 a6989586621679814737 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814738 :: [a]) = Partition a6989586621679814737 a6989586621679814738
type Apply (SpanSym1 a6989586621679814884 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814885 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym1 a6989586621679814884 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814885 :: [a]) = Span a6989586621679814884 a6989586621679814885
type Apply (SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814817 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814817 :: [a]) = SplitAt a6989586621679814816 a6989586621679814817
type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679815359 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679815359 :: [a]) = Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type
type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679348512 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679348512 :: f (a ~> b)) = (<*>@#@$$) a6989586621679348512
type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679532908 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679532908 :: f a) = (<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type
type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679532901 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679532901 :: f a) = ($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type
type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679348472 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679348472 :: f a) = (<**>@#@$$) a6989586621679348472 :: TyFun (f (a ~> b)) (f b) -> Type
type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679348633 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679348633 :: f a) = (<|>@#@$$) a6989586621679348633
type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679348287 :: m (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679348287 :: m (a ~> b)) = ApSym1 a6989586621679348287
type Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) (a6989586621681083542 :: m (a, b)) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MunzipSym0 :: TyFun (m (a, b)) (m a, m b) -> Type) (a6989586621681083542 :: m (a, b)) = Munzip a6989586621681083542
type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679348592 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679348592 :: m a) = (>>=@#@$$) a6989586621679348592 :: TyFun (a ~> m b) (m b) -> Type
type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679348639 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679348639 :: m a) = MplusSym1 a6989586621679348639
type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621681083531 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621681083531 :: m a) = MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type
type Apply (ZipWithSym1 a6989586621681120364 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681120365 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym1 a6989586621681120364 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681120365 :: NonEmpty a) = ZipWithSym2 a6989586621681120364 a6989586621681120365
type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679966021 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679966021 :: [a]) = Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type
type Apply (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679815348 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679815348 :: [a]) = ZipWithSym2 a6989586621679815347 a6989586621679815348
type Apply (Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679815360 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679815360 :: [b]) = Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type
type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679348529 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679348529 :: f a) = (<*@#@$$) a6989586621679348529 :: TyFun (f b) (f a) -> Type
type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679348524 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679348524 :: f a) = (*>@#@$$) a6989586621679348524 :: TyFun (f b) (f b) -> Type
type Apply (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) (x :: f a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Apply (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) (x :: f a) = PairSym1 x :: TyFun (g a) (Product f g a) -> Type
type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679348597 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679348597 :: m a) = (>>@#@$$) a6989586621679348597 :: TyFun (m b) (m b) -> Type
type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621680390332 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621680390332 :: t a) = For_Sym1 a6989586621680390332 :: TyFun (a ~> f b) (f ()) -> Type
type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680741302 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680741302 :: t a) = ForSym1 a6989586621680741302 :: TyFun (a ~> f b) (f (t b)) -> Type
type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621680390312 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621680390312 :: t a) = ForM_Sym1 a6989586621680390312 :: TyFun (a ~> m b) (m ()) -> Type
type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680741291 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680741291 :: t a) = ForMSym1 a6989586621680741291 :: TyFun (a ~> m b) (m (t b)) -> Type
type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679965998 :: [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) (a6989586621679965998 :: [a]) = Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type
type Apply (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679815333 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679815333 :: [a]) = ZipWith3Sym2 a6989586621679815332 a6989586621679815333
type Apply (ZipWithM_Sym1 a6989586621681205305 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621681205306 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithM_Sym1 a6989586621681205305 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621681205306 :: [a]) = ZipWithM_Sym2 a6989586621681205305 a6989586621681205306
type Apply (ZipWithMSym1 a6989586621681205315 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621681205316 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithMSym1 a6989586621681205315 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621681205316 :: [a]) = ZipWithMSym2 a6989586621681205315 a6989586621681205316
type Apply (Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679966022 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679966022 :: [b]) = Zip4Sym2 a6989586621679966021 a6989586621679966022 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type
type Apply (LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679348519 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679348519 :: f a) = LiftA2Sym2 a6989586621679348518 a6989586621679348519
type Apply (MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621681083538 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621681083538 :: m a) = MzipWithSym2 a6989586621681083537 a6989586621681083538
type Apply (LiftM2Sym1 a6989586621679348399 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679348400 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM2Sym1 a6989586621679348399 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679348400 :: m a1) = LiftM2Sym2 a6989586621679348399 a6989586621679348400
type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679965970 :: [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) (a6989586621679965970 :: [a]) = Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type
type Apply (ZipWith4Sym1 a6989586621679965901 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679965902 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym1 a6989586621679965901 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679965902 :: [a]) = ZipWith4Sym2 a6989586621679965901 a6989586621679965902
type Apply (Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679965999 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679965999 :: [b]) = Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type
type Apply (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679815334 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679815334 :: [b]) = ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334
type Apply (Zip4Sym2 a6989586621679966021 a6989586621679966022 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679966023 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym2 a6989586621679966021 a6989586621679966022 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679966023 :: [c]) = Zip4Sym3 a6989586621679966021 a6989586621679966022 a6989586621679966023 :: TyFun [d] [(a, b, c, d)] -> Type
type Apply (LiftA3Sym1 a6989586621679348450 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679348451 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym1 a6989586621679348450 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679348451 :: f a) = LiftA3Sym2 a6989586621679348450 a6989586621679348451
type Apply (LiftM3Sym1 a6989586621679348375 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679348376 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym1 a6989586621679348375 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679348376 :: m a1) = LiftM3Sym2 a6989586621679348375 a6989586621679348376
type Apply (MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type) (a6989586621680741280 :: t b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type) (a6989586621680741280 :: t b) = MapAccumL a6989586621680741278 a6989586621680741279 a6989586621680741280
type Apply (MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: TyFun (t b) (a, t c) -> Type) (a6989586621680741270 :: t b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: TyFun (t b) (a, t c) -> Type) (a6989586621680741270 :: t b) = MapAccumR a6989586621680741268 a6989586621680741269 a6989586621680741270
type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679965937 :: [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) (a6989586621679965937 :: [a]) = Zip7Sym1 a6989586621679965937 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type
type Apply (ZipWith5Sym1 a6989586621679965878 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679965879 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym1 a6989586621679965878 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679965879 :: [a]) = ZipWith5Sym2 a6989586621679965878 a6989586621679965879
type Apply (Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679965971 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679965971 :: [b]) = Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type
type Apply (ZipWith4Sym2 a6989586621679965901 a6989586621679965902 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679965903 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym2 a6989586621679965901 a6989586621679965902 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679965903 :: [b]) = ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903
type Apply (Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679966000 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679966000 :: [c]) = Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type
type Apply (LiftA3Sym2 a6989586621679348450 a6989586621679348451 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679348452 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym2 a6989586621679348450 a6989586621679348451 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679348452 :: f b) = LiftA3Sym3 a6989586621679348450 a6989586621679348451 a6989586621679348452
type Apply (LiftM4Sym1 a6989586621679348344 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679348345 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym1 a6989586621679348344 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679348345 :: m a1) = LiftM4Sym2 a6989586621679348344 a6989586621679348345
type Apply (LiftM3Sym2 a6989586621679348375 a6989586621679348376 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679348377 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym2 a6989586621679348375 a6989586621679348376 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679348377 :: m a2) = LiftM3Sym3 a6989586621679348375 a6989586621679348376 a6989586621679348377
type Apply (ZipWith6Sym1 a6989586621679965851 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679965852 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym1 a6989586621679965851 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679965852 :: [a]) = ZipWith6Sym2 a6989586621679965851 a6989586621679965852
type Apply (Zip7Sym1 a6989586621679965937 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679965938 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym1 a6989586621679965937 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679965938 :: [b]) = Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type
type Apply (ZipWith5Sym2 a6989586621679965878 a6989586621679965879 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679965880 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym2 a6989586621679965878 a6989586621679965879 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679965880 :: [b]) = ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880
type Apply (Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679965972 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679965972 :: [c]) = Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type
type Apply (ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679965904 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679965904 :: [c]) = ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904
type Apply (Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679966001 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679966001 :: [d]) = Zip5Sym4 a6989586621679965998 a6989586621679965999 a6989586621679966000 a6989586621679966001 :: TyFun [e] [(a, b, c, d, e)] -> Type
type Apply (LiftM5Sym1 a6989586621679348306 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679348307 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym1 a6989586621679348306 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679348307 :: m a1) = LiftM5Sym2 a6989586621679348306 a6989586621679348307
type Apply (LiftM4Sym2 a6989586621679348344 a6989586621679348345 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679348346 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym2 a6989586621679348344 a6989586621679348345 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679348346 :: m a2) = LiftM4Sym3 a6989586621679348344 a6989586621679348345 a6989586621679348346
type Apply (ZipWith7Sym1 a6989586621679965820 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679965821 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym1 a6989586621679965820 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679965821 :: [a]) = ZipWith7Sym2 a6989586621679965820 a6989586621679965821
type Apply (ZipWith6Sym2 a6989586621679965851 a6989586621679965852 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679965853 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym2 a6989586621679965851 a6989586621679965852 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679965853 :: [b]) = ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853
type Apply (Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679965939 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679965939 :: [c]) = Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type
type Apply (ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679965881 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679965881 :: [c]) = ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881
type Apply (Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679965973 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679965973 :: [d]) = Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type
type Apply (LiftM5Sym2 a6989586621679348306 a6989586621679348307 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679348308 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym2 a6989586621679348306 a6989586621679348307 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679348308 :: m a2) = LiftM5Sym3 a6989586621679348306 a6989586621679348307 a6989586621679348308
type Apply (LiftM4Sym3 a6989586621679348344 a6989586621679348345 a6989586621679348346 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679348347 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym3 a6989586621679348344 a6989586621679348345 a6989586621679348346 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679348347 :: m a3) = LiftM4Sym4 a6989586621679348344 a6989586621679348345 a6989586621679348346 a6989586621679348347
type Apply (ZipWith7Sym2 a6989586621679965820 a6989586621679965821 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679965822 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym2 a6989586621679965820 a6989586621679965821 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679965822 :: [b]) = ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822
type Apply (ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679965854 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679965854 :: [c]) = ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854
type Apply (Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679965940 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679965940 :: [d]) = Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type
type Apply (ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679965882 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679965882 :: [d]) = ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882
type Apply (Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679965974 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679965974 :: [e]) = Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type
type Apply (LiftM5Sym3 a6989586621679348306 a6989586621679348307 a6989586621679348308 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679348309 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym3 a6989586621679348306 a6989586621679348307 a6989586621679348308 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679348309 :: m a3) = LiftM5Sym4 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309
type Apply (ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679965823 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679965823 :: [c]) = ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823
type Apply (ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679965855 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679965855 :: [d]) = ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855
type Apply (Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679965941 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679965941 :: [e]) = Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type
type Apply (LiftM5Sym4 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679348310 :: m a4) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym4 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679348310 :: m a4) = LiftM5Sym5 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 a6989586621679348310
type Apply (ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679965824 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679965824 :: [d]) = ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824
type Apply (ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679965856 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679965856 :: [e]) = ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856
type Apply (Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679965942 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679965942 :: [f]) = Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type
type Apply (ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679965825 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679965825 :: [e]) = ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825
type Apply (ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679965826 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679965826 :: [f]) = ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826
type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679815295 :: [(a, b, c)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679815295 :: [(a, b, c)]) = Unzip3 a6989586621679815295
type Apply (Unzip4Sym0 :: TyFun [(a, b, c, d)] ([a], [b], [c], [d]) -> Type) (a6989586621679815275 :: [(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) (a6989586621679815275 :: [(a, b, c, d)]) = Unzip4 a6989586621679815275
type Apply (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) (x :: f a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

type Apply (InLSym0 :: TyFun (f a) (Sum f g a) -> Type) (x :: f a) = 'InL x :: Sum f g a
type Apply (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) (y :: g a) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

type Apply (InRSym0 :: TyFun (g a) (Sum f g a) -> Type) (y :: g a) = 'InR y :: Sum f g a
type Apply (PairSym1 x :: TyFun (g a) (Product f g a) -> Type) (y :: g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Apply (PairSym1 x :: TyFun (g a) (Product f g a) -> Type) (y :: g a) = 'Pair x y
type Apply (Unzip5Sym0 :: TyFun [(a, b, c, d, e)] ([a], [b], [c], [d], [e]) -> Type) (a6989586621679815253 :: [(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) (a6989586621679815253 :: [(a, b, c, d, e)]) = Unzip5 a6989586621679815253
type Apply (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) (x :: f (g a)) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

type Apply (ComposeSym0 :: TyFun (f (g a)) (Compose f g a) -> Type) (x :: f (g a)) = 'Compose x
type Apply (Unzip6Sym0 :: TyFun [(a, b, c, d, e, f)] ([a], [b], [c], [d], [e], [f]) -> Type) (a6989586621679815229 :: [(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) (a6989586621679815229 :: [(a, b, c, d, e, f)]) = Unzip6 a6989586621679815229
type Apply (Unzip7Sym0 :: TyFun [(a, b, c, d, e, f, g)] ([a], [b], [c], [d], [e], [f], [g]) -> Type) (a6989586621679815203 :: [(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) (a6989586621679815203 :: [(a, b, c, d, e, f, g)]) = Unzip7 a6989586621679815203
type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679337100 :: Either a b) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (IsLeftSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679337100 :: Either a b) = IsLeft a6989586621679337100
type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679337097 :: Either a b) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (IsRightSym0 :: TyFun (Either a b) Bool -> Type) (a6989586621679337097 :: Either a b) = IsRight a6989586621679337097
type Apply (FstSym0 :: TyFun (a, b) a -> Type) (a6989586621679172905 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (FstSym0 :: TyFun (a, b) a -> Type) (a6989586621679172905 :: (a, b)) = Fst a6989586621679172905
type Apply (SndSym0 :: TyFun (a, b) b -> Type) (a6989586621679172901 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (SndSym0 :: TyFun (a, b) b -> Type) (a6989586621679172901 :: (a, b)) = Snd a6989586621679172901
type Apply ((&@#@$$) a6989586621679327005 :: TyFun (a ~> b) b -> Type) (a6989586621679327006 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply ((&@#@$$) a6989586621679327005 :: TyFun (a ~> b) b -> Type) (a6989586621679327006 :: a ~> b) = a6989586621679327005 & a6989586621679327006
type Apply (UncurrySym1 a6989586621679172885 :: TyFun (a, b) c -> Type) (a6989586621679172886 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym1 a6989586621679172885 :: TyFun (a, b) c -> Type) (a6989586621679172886 :: (a, b)) = Uncurry a6989586621679172885 a6989586621679172886
type Apply (Either_Sym2 a6989586621679334944 a6989586621679334945 :: TyFun (Either a b) c -> Type) (a6989586621679334946 :: Either a b) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym2 a6989586621679334944 a6989586621679334945 :: TyFun (Either a b) c -> Type) (a6989586621679334946 :: Either a b) = Either_ a6989586621679334944 a6989586621679334945 a6989586621679334946
type Apply ((<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679532909 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679532909 :: a ~> b) = a6989586621679532908 <&> a6989586621679532909
type Apply ((>>=@#@$$) a6989586621679348592 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679348593 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$$) a6989586621679348592 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679348593 :: a ~> m b) = a6989586621679348592 >>= a6989586621679348593
type Apply (For_Sym1 a6989586621680390332 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680390333 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym1 a6989586621680390332 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680390333 :: a ~> f b) = For_ a6989586621680390332 a6989586621680390333
type Apply (ForSym1 a6989586621680741302 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680741303 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForSym1 a6989586621680741302 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680741303 :: a ~> f b) = For a6989586621680741302 a6989586621680741303
type Apply (ForM_Sym1 a6989586621680390312 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680390313 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym1 a6989586621680390312 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680390313 :: a ~> m b) = ForM_ a6989586621680390312 a6989586621680390313
type Apply (ForMSym1 a6989586621680741291 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680741292 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForMSym1 a6989586621680741291 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680741292 :: a ~> m b) = ForM a6989586621680741291 a6989586621680741292
type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621680208653 a6989586621680208654
type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) = ShowListWithSym1 a6989586621680208688
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120308 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120308 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621681120308
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679815130 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679815130 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621679815130
type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815110 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815110 :: a ~> (a ~> Ordering)) = InsertBySym1 a6989586621679815110
type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120430 :: 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) (a6989586621681120430 :: a ~> (a ~> Bool)) = GroupBy1Sym1 a6989586621681120430
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120321 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120321 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621681120321
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679815142 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679815142 :: a ~> (a ~> Bool)) = DeleteFirstsBySym1 a6989586621679815142
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814967 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814967 :: a ~> (a ~> Bool)) = IntersectBySym1 a6989586621679814967
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814606 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814606 :: a ~> (a ~> Bool)) = UnionBySym1 a6989586621679814606
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120482 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120482 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621681120482
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679814759 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679814759 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621679814759
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679814626 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679814626 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621679814626
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815152 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815152 :: a ~> (a ~> Bool)) = DeleteBySym1 a6989586621679815152
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120626 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120626 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621681120626
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120618 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120618 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621681120618
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815582 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815582 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679815582
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815544 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815544 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679815544
type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679815658 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679815658 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679815658
type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120540 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120540 :: a ~> Bool) = BreakSym1 a6989586621681120540
type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120522 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120522 :: a ~> Bool) = PartitionSym1 a6989586621681120522
type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120549 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120549 :: a ~> Bool) = SpanSym1 a6989586621681120549
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120558 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120558 :: a ~> Bool) = DropWhileSym1 a6989586621681120558
type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120531 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120531 :: a ~> Bool) = FilterSym1 a6989586621681120531
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120567 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120567 :: a ~> Bool) = TakeWhileSym1 a6989586621681120567
type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679180149 :: a ~> Bool) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679180149 :: a ~> Bool) = UntilSym1 a6989586621679180149
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679815019 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679815019 :: a ~> Bool) = FindIndexSym1 a6989586621679815019
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814849 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814849 :: a ~> Bool) = BreakSym1 a6989586621679814849
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814737 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814737 :: a ~> Bool) = PartitionSym1 a6989586621679814737
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814884 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814884 :: a ~> Bool) = SpanSym1 a6989586621679814884
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679814996 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679814996 :: a ~> Bool) = FindIndicesSym1 a6989586621679814996
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814921 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814921 :: a ~> Bool) = DropWhileEndSym1 a6989586621679814921
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814938 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814938 :: a ~> Bool) = DropWhileSym1 a6989586621679814938
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679815053 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679815053 :: a ~> Bool) = FilterSym1 a6989586621679815053
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814953 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814953 :: a ~> Bool) = TakeWhileSym1 a6989586621679814953
type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390215 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390215 :: a ~> (a ~> Ordering)) = MaximumBySym1 a6989586621680390215 :: TyFun (t a) a -> Type
type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390195 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390195 :: a ~> (a ~> Ordering)) = MinimumBySym1 a6989586621680390195 :: TyFun (t a) a -> Type
type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390425 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390425 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type
type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390420 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390420 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120637 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120637 :: a ~> (b ~> b)) = ScanrSym1 a6989586621681120637
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815564 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815564 :: a ~> (b ~> b)) = ScanrSym1 a6989586621679815564
type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679579760 :: a ~> Maybe b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679579760 :: a ~> Maybe b) = MapMaybeSym1 a6989586621679579760
type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681120784 :: 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) (a6989586621681120784 :: a ~> (b, Maybe a)) = UnfoldSym1 a6989586621681120784
type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681120749 :: 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) (a6989586621681120749 :: a ~> (b, Maybe a)) = UnfoldrSym1 a6989586621681120749
type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621681205203 :: a ~> Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621681205203 :: a ~> Bool) = MfilterSym1 a6989586621681205203 :: TyFun (m a) (m a) -> Type
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680390168 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680390168 :: a ~> Bool) = FindSym1 a6989586621680390168 :: TyFun (t a) (Maybe a) -> Type
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390235 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390235 :: a ~> Bool) = AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390244 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390244 :: a ~> Bool) = AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type
type Apply (UntilSym1 a6989586621679180149 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679180150 :: a ~> a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym1 a6989586621679180149 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679180150 :: a ~> a) = UntilSym2 a6989586621679180149 a6989586621679180150
type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120414 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120414 :: a ~> b) = GroupAllWith1Sym1 a6989586621681120414
type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120423 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120423 :: a ~> b) = GroupWith1Sym1 a6989586621681120423
type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621681120679 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621681120679 :: a ~> b) = MapSym1 a6989586621681120679
type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120464 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120464 :: a ~> b) = GroupAllWithSym1 a6989586621681120464
type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120473 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120473 :: a ~> b) = GroupWithSym1 a6989586621681120473
type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679180239 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679180239 :: a ~> b) = MapSym1 a6989586621679180239
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) (a6989586621679180167 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679180167 :: a ~> b) = ($!@#@$$) a6989586621679180167
type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679180176 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679180176 :: a ~> b) = ($@#@$$) a6989586621679180176
type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621681205365 :: a ~> m Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621681205365 :: a ~> m Bool) = FilterMSym1 a6989586621681205365
type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120299 :: a ~> o) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120299 :: a ~> o) = SortWithSym1 a6989586621681120299
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120649 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120649 :: b ~> (a ~> b)) = ScanlSym1 a6989586621681120649
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815591 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815591 :: b ~> (a ~> b)) = ScanlSym1 a6989586621679815591
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679815436 :: b ~> Maybe (a, b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679815436 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679815436
type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679237099 :: b ~> a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679237099 :: b ~> a) = ComparingSym1 a6989586621679237099
type Apply (SwapSym0 :: TyFun (a, b) (b, a) -> Type) (a6989586621679172879 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (SwapSym0 :: TyFun (a, b) (b, a) -> Type) (a6989586621679172879 :: (a, b)) = Swap a6989586621679172879
type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679172893 :: (a, b) ~> c) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679172893 :: (a, b) ~> c) = CurrySym1 a6989586621679172893
type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390400 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390400 :: a ~> (b ~> b)) = Foldr'Sym1 a6989586621680390400 :: TyFun b (t a ~> b) -> Type
type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390393 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390393 :: a ~> (b ~> b)) = FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621681120364 :: 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) (a6989586621681120364 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621681120364
type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679172885 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679172885 :: a ~> (b ~> c)) = UncurrySym1 a6989586621679172885
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679815347 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679815347 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621679815347
type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679180195 :: a ~> (b ~> c)) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679180195 :: a ~> (b ~> c)) = FlipSym1 a6989586621679180195
type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680390263 :: a ~> [b]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680390263 :: a ~> [b]) = ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type
type Apply (Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679577735 :: a ~> b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679577735 :: a ~> b) = Maybe_Sym2 a6989586621679577734 a6989586621679577735
type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348484 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348484 :: a ~> b) = FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type
type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348461 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348461 :: a ~> b) = LiftASym1 a6989586621679348461 :: TyFun (f a) (f b) -> Type
type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679532919 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679532919 :: a ~> b) = (<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type
type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621681205219 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621681205219 :: a ~> b) = (<$!>@#@$$) a6989586621681205219 :: TyFun (m a) (m b) -> Type
type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680741254 :: a ~> b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680741254 :: a ~> b) = FmapDefaultSym1 a6989586621680741254 :: TyFun (t a) (t b) -> Type
type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679334944 :: a ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679334944 :: a ~> c) = Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type
type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680390387 :: a ~> m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680390387 :: a ~> m) = FoldMapSym1 a6989586621680390387 :: TyFun (t a) m -> Type
type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680741235 :: a ~> m) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680741235 :: a ~> m) = FoldMapDefaultSym1 a6989586621680741235 :: TyFun (t a) m -> Type
type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679348437 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679348437 :: a ~> m b) = (=<<@#@$$) a6989586621679348437
type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679348416 :: a1 ~> r) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679348416 :: a1 ~> r) = LiftMSym1 a6989586621679348416 :: TyFun (m a1) (m r) -> Type
type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390414 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390414 :: b ~> (a ~> b)) = Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type
type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390407 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390407 :: b ~> (a ~> b)) = FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type
type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679327018 :: b ~> (b ~> c)) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679327018 :: b ~> (b ~> c)) = OnSym1 a6989586621679327018 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type
type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679180207 :: b ~> c) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679180207 :: b ~> c) = (.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type
type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679815332 :: 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) (a6989586621679815332 :: a ~> (b ~> (c ~> d))) = ZipWith3Sym1 a6989586621679815332
type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680741278 :: 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) (a6989586621680741278 :: a ~> (b ~> (a, c))) = MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type
type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680741268 :: 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) (a6989586621680741268 :: a ~> (b ~> (a, c))) = MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type
type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679348518 :: 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) (a6989586621679348518 :: a ~> (b ~> c)) = LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type
type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621681083537 :: 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) (a6989586621681083537 :: a ~> (b ~> c)) = MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type
type Apply (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621680390367 :: 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) (a6989586621680390367 :: a ~> (b ~> m b)) = FoldrMSym1 a6989586621680390367 :: TyFun b (t a ~> m b) -> Type
type Apply (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) (a6989586621681205305 :: 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) (a6989586621681205305 :: a ~> (b ~> m c)) = ZipWithM_Sym1 a6989586621681205305
type Apply (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) (a6989586621681205315 :: 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) (a6989586621681205315 :: a ~> (b ~> m c)) = ZipWithMSym1 a6989586621681205315
type Apply (OnSym1 a6989586621679327018 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679327019 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym1 a6989586621679327018 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679327019 :: a ~> b) = OnSym2 a6989586621679327018 a6989586621679327019
type Apply ((.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679180208 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679180208 :: a ~> b) = a6989586621679180207 .@#@$$$ a6989586621679180208
type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621680390341 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621680390341 :: a ~> f b) = Traverse_Sym1 a6989586621680390341 :: TyFun (t a) (f ()) -> Type
type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680733986 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680733986 :: a ~> f b) = TraverseSym1 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type
type Apply (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) (a6989586621681205324 :: 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) (a6989586621681205324 :: a ~> m (b, c)) = MapAndUnzipMSym1 a6989586621681205324
type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621681205350 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621681205350 :: a ~> m b) = (>=>@#@$$) a6989586621681205350 :: TyFun (b ~> m c) (a ~> m c) -> Type
type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621680390321 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621680390321 :: a ~> m b) = MapM_Sym1 a6989586621680390321 :: TyFun (t a) (m ()) -> Type
type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680733994 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680733994 :: a ~> m b) = MapMSym1 a6989586621680733994 :: TyFun (t a) (m (t b)) -> Type
type Apply (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) (a6989586621679348399 :: 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) (a6989586621679348399 :: a1 ~> (a2 ~> r)) = LiftM2Sym1 a6989586621679348399 :: TyFun (m a1) (m a2 ~> m r) -> Type
type Apply (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621680390349 :: 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) (a6989586621680390349 :: b ~> (a ~> m b)) = FoldlMSym1 a6989586621680390349 :: TyFun b (t a ~> m b) -> Type
type Apply (Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679334945 :: b ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679334945 :: b ~> c) = Either_Sym2 a6989586621679334944 a6989586621679334945
type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621681205338 :: b ~> m c) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621681205338 :: b ~> m c) = (<=<@#@$$) a6989586621681205338 :: TyFun (a ~> m b) (a ~> m c) -> Type
type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679965901 :: 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) (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) = ZipWith4Sym1 a6989586621679965901
type Apply (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) (a6989586621679348450 :: 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) (a6989586621679348450 :: a ~> (b ~> (c ~> d))) = LiftA3Sym1 a6989586621679348450 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type
type Apply ((<=<@#@$$) a6989586621681205338 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621681205339 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<=<@#@$$) a6989586621681205338 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621681205339 :: a ~> m b) = a6989586621681205338 <=<@#@$$$ a6989586621681205339
type Apply (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) (a6989586621679348375 :: 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) (a6989586621679348375 :: a1 ~> (a2 ~> (a3 ~> r))) = LiftM3Sym1 a6989586621679348375 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type
type Apply ((>=>@#@$$) a6989586621681205350 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621681205351 :: b ~> m c) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((>=>@#@$$) a6989586621681205350 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621681205351 :: b ~> m c) = a6989586621681205350 >=>@#@$$$ a6989586621681205351
type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679965878 :: 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) (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) = ZipWith5Sym1 a6989586621679965878
type Apply (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) (a6989586621679348344 :: 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) (a6989586621679348344 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) = LiftM4Sym1 a6989586621679348344 :: 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) (a6989586621679965851 :: 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) (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) = ZipWith6Sym1 a6989586621679965851
type Apply (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) (a6989586621679348306 :: 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) (a6989586621679348306 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) = LiftM5Sym1 a6989586621679348306 :: 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) (a6989586621679965820 :: 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) (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) = ZipWith7Sym1 a6989586621679965820
type Apply (GetConstSym0 :: TyFun (Const a b) a -> Type) (a6989586621680681956 :: Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Apply (GetConstSym0 :: TyFun (Const a b) a -> Type) (a6989586621680681956 :: Const a b) = GetConst a6989586621680681956
type Apply (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) (a6989586621681192397 :: 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) (a6989586621681192397 :: Compose f g a) = GetCompose a6989586621681192397

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 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 Void Source # 
Instance details

Defined in Data.Singletons.Base.Instances

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 (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 (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 (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 (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

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 (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 (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Demote (Arg a b) = Arg (Demote a) (Demote b)
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 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 (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 ('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 ('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 ('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) #

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

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

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

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

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

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

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

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

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

(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 x => SingI1 ('Pair x :: g a -> Product f g a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

liftSing :: forall (x0 :: g a). Sing x0 -> Sing ('Pair x x0) #

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 

type TyCon1 = TyCon :: (k1 -> k2) -> k1 ~> k2 #

type TyCon2 = TyCon :: (k1 -> k2 -> k3) -> k1 ~> (k2 ~> k3) #

type TyCon3 = TyCon :: (k1 -> k2 -> k3 -> k4) -> k1 ~> (k2 ~> (k3 ~> k4)) #

type TyCon4 = TyCon :: (k1 -> k2 -> k3 -> k4 -> k5) -> k1 ~> (k2 ~> (k3 ~> (k4 ~> k5))) #

type TyCon5 = TyCon :: (k1 -> k2 -> k3 -> k4 -> k5 -> k6) -> k1 ~> (k2 ~> (k3 ~> (k4 ~> (k5 ~> k6)))) #

type TyCon6 = TyCon :: (k1 -> k2 -> k3 -> k4 -> k5 -> k6 -> k7) -> k1 ~> (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> k7))))) #

type TyCon7 = TyCon :: (k1 -> k2 -> k3 -> k4 -> k5 -> k6 -> k7 -> k8) -> k1 ~> (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> k8)))))) #

type TyCon8 = TyCon :: (k1 -> k2 -> k3 -> k4 -> k5 -> k6 -> k7 -> k8 -> k9) -> k1 ~> (k2 ~> (k3 ~> (k4 ~> (k5 ~> (k6 ~> (k7 ~> (k8 ~> k9))))))) #

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

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

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

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

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

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

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

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

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

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

(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 (MemptySym0 :: a ~> b) Source #

sMappend :: forall (t1 :: a ~> b) (t2 :: a ~> b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a ~> b) ((a ~> b) ~> (a ~> b)) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [a ~> b]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [a ~> b] (a ~> b) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (a ~> b) ((a ~> b) ~> (a ~> b)) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a ~> b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a ~> b)) (a ~> b) -> Type) t) Source #

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 XorSym0 Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

Methods

sing :: Sing XorSym0 #

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 GetAllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings GetAnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings XorSym0 Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

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

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

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

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

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 (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 (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 (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 (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 (ShowParenSym1 a6989586621680208653 :: 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 (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 (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 a6989586621679566965 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (ModSym1 a6989586621679567401 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (QuotSym1 a6989586621679568006 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (RemSym1 a6989586621679567995 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings ((^@#@$$) a6989586621679556329 :: TyFun Natural Natural -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

SuppressUnusedWarnings (DivModSym1 a6989586621679568024 :: TyFun Natural (Natural, Natural) -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (QuotRemSym1 a6989586621679568017 :: 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 (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 ((&&@#@$$) a6989586621679132115 :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings ((||@#@$$) a6989586621679132472 :: 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 a6989586621679569296 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowStringSym1 a6989586621680208669 :: 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 (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 (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 (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 (JustSym0 :: TyFun a (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (FromEnumSym0 :: TyFun a Natural -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

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

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

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

SingI d => SingI (FromMaybeSym1 d :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

Methods

sing :: Sing (FromMaybeSym1 d) #

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

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

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 (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 (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 (UnzipSym0 :: TyFun (NonEmpty (a, b)) (NonEmpty a, NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupBy1Sym1 a6989586621681120430 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((<|@#@$$) a6989586621681120723 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ConsSym1 a6989586621681120716 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IntersperseSym1 a6989586621681120607 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (NubBySym1 a6989586621681120321 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Scanl1Sym1 a6989586621681120626 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (Scanr1Sym1 a6989586621681120618 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SortBySym1 a6989586621681120308 :: 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 a6989586621681120540 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (PartitionSym1 a6989586621681120522 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SpanSym1 a6989586621681120549 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SplitAtSym1 a6989586621681120576 :: TyFun (NonEmpty a) ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621681120403 :: TyFun (NonEmpty a) Bool -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DropSym1 a6989586621681120585 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DropWhileSym1 a6989586621681120558 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (FilterSym1 a6989586621681120531 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TakeSym1 a6989586621681120594 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (TakeWhileSym1 a6989586621681120567 :: TyFun (NonEmpty a) [a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.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 a6989586621679180149 :: 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 ((:$$:@#@$$) a6989586621680205232 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings ((:<>:@#@$$) a6989586621680205229 :: TyFun (ErrorMessage' s) (ErrorMessage' s) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

SuppressUnusedWarnings (FromMaybeSym1 a6989586621679579790 :: TyFun (Maybe a) a -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

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 ((!!@#@$$) a6989586621681120384 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((!!@#@$$) a6989586621679814661 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

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 (IntercalateSym1 a6989586621679815772 :: TyFun [[a]] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertSym1 a6989586621681120660 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings ((:|@#@$$) a6989586621679046311 :: TyFun [a] (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (DeleteFirstsBySym1 a6989586621679815142 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersectBySym1 a6989586621679814967 :: TyFun [a] ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnionBySym1 a6989586621679814606 :: 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 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ElemIndexSym1 a6989586621679815037 :: TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FindIndexSym1 a6989586621679815019 :: TyFun [a] (Maybe Natural) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (StripPrefixSym1 a6989586621679966032 :: TyFun [a] (Maybe [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (BreakSym1 a6989586621679814849 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (PartitionSym1 a6989586621679814737 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SpanSym1 a6989586621679814884 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsInfixOfSym1 a6989586621679815396 :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsPrefixOfSym1 a6989586621679815410 :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IsSuffixOfSym1 a6989586621679815403 :: TyFun [a] Bool -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GroupBySym1 a6989586621681120482 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ElemIndicesSym1 a6989586621679815028 :: TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FindIndicesSym1 a6989586621679814996 :: TyFun [a] [Natural] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GroupBySym1 a6989586621679814759 :: TyFun [a] [[a]] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DeleteSym1 a6989586621679815182 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropSym1 a6989586621679814823 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropWhileEndSym1 a6989586621679814921 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DropWhileSym1 a6989586621679814938 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (FilterSym1 a6989586621679815053 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertSym1 a6989586621679814791 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersectSym1 a6989586621679814989 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersperseSym1 a6989586621679815779 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (NubBySym1 a6989586621679814626 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Scanl1Sym1 a6989586621679815582 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Scanr1Sym1 a6989586621679815544 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (SortBySym1 a6989586621679815130 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TakeSym1 a6989586621679814836 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (TakeWhileSym1 a6989586621679814953 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnionSym1 a6989586621679814598 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ((\\@#@$$) a6989586621679815171 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings ((:@#@$$) a6989586621679046238 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings ((++@#@$$) a6989586621679180230 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (Foldl1'Sym1 a6989586621679815658 :: 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 a6989586621680208723 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsSym1 a6989586621680208706 :: 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 a6989586621679237108 :: 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 a6989586621679130897 :: 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 a6989586621679815152 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertBySym1 a6989586621679815110 :: TyFun a ([a] ~> [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (EnumFromThenToSym1 a6989586621679612942 :: 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 ((/=@#@$$) a6989586621679137923 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((==@#@$$) a6989586621679137918 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((<=@#@$$) a6989586621679237118 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((<@#@$$) a6989586621679237113 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((>=@#@$$) a6989586621679237128 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((>@#@$$) a6989586621679237123 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (EnumFromToSym1 a6989586621679612936 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (MappendSym1 a6989586621680292326 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (MaxSym1 a6989586621679237133 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (MinSym1 a6989586621679237138 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings ((<>@#@$$) a6989586621679207889 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

SuppressUnusedWarnings (AsTypeOfSym1 a6989586621679180187 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings ((*@#@$$) a6989586621679590952 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings ((+@#@$$) a6989586621679590942 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings ((-@#@$$) a6989586621679590947 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

SuppressUnusedWarnings (SubtractSym1 a6989586621679590935 :: 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 a6989586621681205232 :: TyFun (f ()) (f ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (WhenSym1 a6989586621679348427 :: TyFun (f ()) (f ()) -> 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 a6989586621679133031 :: TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (DefaultEqSym1 a6989586621679140066 :: TyFun k Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

SuppressUnusedWarnings ((<=?@#@$$) a6989586621679556760 :: TyFun k Bool -> Type) Source # 
Instance details

Defined in GHC.TypeLits.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 (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) #

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

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

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

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

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

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

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

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

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

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

(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 (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 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 (GetConstSym0 :: TyFun (Const a b) a -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

SuppressUnusedWarnings (GroupAllWith1Sym1 a6989586621681120414 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupWith1Sym1 a6989586621681120423 :: TyFun (NonEmpty a) (NonEmpty (NonEmpty a)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (SortWithSym1 a6989586621681120299 :: TyFun (NonEmpty a) (NonEmpty a) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (MapSym1 a6989586621681120679 :: TyFun (NonEmpty a) (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ZipSym1 a6989586621681120375 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.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 a6989586621679577734 :: 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 ((&@#@$$) a6989586621679327005 :: 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 a6989586621679130897 a6989586621679130898 :: TyFun Bool a -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

SuppressUnusedWarnings (LookupSym1 a6989586621679814744 :: 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 (FailSym0 :: TyFun [Char] (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

SuppressUnusedWarnings (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (GroupAllWithSym1 a6989586621681120464 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (GroupWithSym1 a6989586621681120473 :: TyFun [a] [NonEmpty a] -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (DeleteBySym2 a6989586621679815152 a6989586621679815153 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (InsertBySym2 a6989586621679815110 a6989586621679815111 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (IntersectBySym2 a6989586621679814967 a6989586621679814968 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (UnionBySym2 a6989586621679814606 a6989586621679814607 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (MapMaybeSym1 a6989586621679579760 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (MapSym1 a6989586621679180239 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (FilterMSym1 a6989586621681205365 :: TyFun [a] (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ShowListWithSym2 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (UnfoldSym1 a6989586621681120784 :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (UnfoldrSym1 a6989586621681120749 :: TyFun a (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.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 a6989586621679612942 a6989586621679612943 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (UntilSym2 a6989586621679180149 a6989586621679180150 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (($!@#@$$) a6989586621679180167 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (($@#@$$) a6989586621679180176 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (ArgSym1 a6989586621680862528 :: TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

SuppressUnusedWarnings (ScanlSym1 a6989586621681120649 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanrSym1 a6989586621681120637 :: TyFun b ([a] ~> NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ComparingSym1 a6989586621679237099 :: TyFun b (b ~> Ordering) -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (Tuple2Sym1 a6989586621679046729 :: TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (UnfoldrSym1 a6989586621679815436 :: TyFun b [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ConstSym1 a6989586621679180220 :: TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (SeqSym1 a6989586621679180140 :: 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 a ~> f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (IfSym2 a6989586621679133031 a6989586621679133032 :: 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 (MplusSym0 :: TyFun (m a) (m a ~> m a) -> 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 (ReplicateM_Sym1 a6989586621681205242 :: TyFun (m a) (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ReplicateMSym1 a6989586621681205260 :: TyFun (m a) (m [a]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (MfilterSym1 a6989586621681205203 :: TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (AsProxyTypeOfSym1 a6989586621680355908 :: TyFun (proxy a) a -> Type) Source # 
Instance details

Defined in Data.Proxy.Singletons

SuppressUnusedWarnings (FindSym1 a6989586621680390168 :: TyFun (t a) (Maybe 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 (AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ElemSym1 a6989586621680390439 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> 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 (Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MaximumBySym1 a6989586621680390215 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MinimumBySym1 a6989586621680390195 :: 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 (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 (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) #

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

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

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

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

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

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

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

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

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

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

(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 a6989586621681120364 :: 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 a6989586621679327018 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

SuppressUnusedWarnings ((.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings ((<&>@#@$$) a6989586621679532908 :: 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 ((>>=@#@$$) a6989586621679348592 :: 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 a6989586621679334944 :: 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 a6989586621679577734 a6989586621679577735 :: TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

SuppressUnusedWarnings (UncurrySym1 a6989586621679172885 :: 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 a6989586621681120649 a6989586621681120650 :: TyFun [a] (NonEmpty b) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

SuppressUnusedWarnings (ScanrSym2 a6989586621681120637 a6989586621681120638 :: 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 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ScanlSym2 a6989586621679815591 a6989586621679815592 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ScanrSym2 a6989586621679815564 a6989586621679815565 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip3Sym1 a6989586621679815359 :: 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 a6989586621679172893 :: TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (ComparingSym2 a6989586621679237099 a6989586621679237100 :: TyFun b Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

SuppressUnusedWarnings (FlipSym1 a6989586621679180195 :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (Tuple3Sym1 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr'Sym1 a6989586621680390400 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings ((<**>@#@$$) a6989586621679348472 :: TyFun (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 ((<|>@#@$$) a6989586621679348633 :: TyFun (f a) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<*>@#@$$) a6989586621679348512 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftASym1 a6989586621679348461 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

SuppressUnusedWarnings ((<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MplusSym1 a6989586621679348639 :: TyFun (m a) (m a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<$!>@#@$$) a6989586621681205219 :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings ((=<<@#@$$) a6989586621679348437 :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (ApSym1 a6989586621679348287 :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftMSym1 a6989586621679348416 :: TyFun (m a1) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

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 a6989586621680390263 :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldMapSym1 a6989586621680390387 :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldMapDefaultSym1 a6989586621680741235 :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (FmapDefaultSym1 a6989586621680741254 :: TyFun (t a) (t b) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (AsumSym0 :: TyFun (t (f a)) (f a) -> 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

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

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

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

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

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

(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, 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 (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 x => SingI (PairSym1 x :: TyFun (g a) (Product f g a) -> Type) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Methods

sing :: Sing (PairSym1 x :: TyFun (g a) (Product f g a) -> 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 (Either_Sym2 a6989586621679334944 a6989586621679334945 :: TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

SuppressUnusedWarnings (GetComposeSym0 :: TyFun (Compose f g a) (f (g a)) -> Type) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

SuppressUnusedWarnings (ZipWithSym2 a6989586621681120364 a6989586621681120365 :: TyFun (NonEmpty b) (NonEmpty c) -> Type) Source # 
Instance details

Defined in Data.List.NonEmpty.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 a6989586621680390332 :: TyFun (a ~> f b) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ForSym1 a6989586621680741302 :: TyFun (a ~> f b) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings ((<=<@#@$$) a6989586621681205338 :: TyFun (a ~> m b) (a ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ForM_Sym1 a6989586621680390312 :: TyFun (a ~> m b) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (ForMSym1 a6989586621680741291 :: 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 ((>=>@#@$$) a6989586621681205350 :: 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 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWithM_Sym1 a6989586621681205305 :: TyFun [a] ([b] ~> m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ZipWithMSym1 a6989586621681205315 :: TyFun [a] ([b] ~> m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (MapAndUnzipMSym1 a6989586621681205324 :: TyFun [a] (m ([b], [c])) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWithSym2 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (OnSym2 a6989586621679327018 a6989586621679327019 :: 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 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (a6989586621679180207 .@#@$$$ a6989586621679180208 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (FlipSym2 a6989586621679180195 a6989586621679180196 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

SuppressUnusedWarnings (Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (FoldlMSym1 a6989586621680390349 :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrMSym1 a6989586621680390367 :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (CurrySym2 a6989586621679172893 a6989586621679172894 :: TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

SuppressUnusedWarnings (Tuple3Sym2 a6989586621679046760 a6989586621679046761 :: TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((<*@#@$$) a6989586621679348529 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((*>@#@$$) a6989586621679348524 :: TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

SuppressUnusedWarnings (LiftM2Sym1 a6989586621679348399 :: TyFun (m a1) (m a2 ~> m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings ((>>@#@$$) a6989586621679348597 :: TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Foldr'Sym2 a6989586621680390400 a6989586621680390401 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Traverse_Sym1 a6989586621680390341 :: TyFun (t a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (TraverseSym1 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (MapM_Sym1 a6989586621680390321 :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MapMSym1 a6989586621680733994 :: 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 a6989586621679965901 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWithM_Sym2 a6989586621681205305 a6989586621681205306 :: TyFun [b] (m ()) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (ZipWithMSym2 a6989586621681205315 a6989586621681205316 :: TyFun [b] (m [c]) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Zip4Sym2 a6989586621679966021 a6989586621679966022 :: 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 a6989586621679327018 a6989586621679327019 a6989586621679327020 :: TyFun a c -> Type) Source # 
Instance details

Defined in Data.Function.Singletons

SuppressUnusedWarnings (a6989586621681205338 <=<@#@$$$ a6989586621681205339 :: TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (a6989586621681205350 >=>@#@$$$ a6989586621681205351 :: TyFun a (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons

SuppressUnusedWarnings (Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftA3Sym1 a6989586621679348450 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftA2Sym2 a6989586621679348518 a6989586621679348519 :: TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM3Sym1 a6989586621679348375 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM2Sym2 a6989586621679348399 a6989586621679348400 :: TyFun (m a2) (m r) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (MzipWithSym2 a6989586621681083537 a6989586621681083538 :: TyFun (m b) (m c) -> Type) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

SuppressUnusedWarnings (FoldlMSym2 a6989586621680390349 a6989586621680390350 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (FoldrMSym2 a6989586621680390367 a6989586621680390368 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

SuppressUnusedWarnings (MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: 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 a6989586621679965878 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith4Sym2 a6989586621679965901 a6989586621679965902 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip4Sym3 a6989586621679966021 a6989586621679966022 a6989586621679966023 :: 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 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple4Sym3 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: TyFun d (a, b, c, d) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftA3Sym2 a6989586621679348450 a6989586621679348451 :: TyFun (f b) (f c ~> f d) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM4Sym1 a6989586621679348344 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM3Sym2 a6989586621679348375 a6989586621679348376 :: 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 a6989586621679965851 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym1 a6989586621679965937 :: 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 a6989586621679965878 a6989586621679965879 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 :: TyFun [c] ([d] ~> [e]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym1 a6989586621679047084 :: 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 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftA3Sym3 a6989586621679348450 a6989586621679348451 a6989586621679348452 :: TyFun (f c) (f d) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM5Sym1 a6989586621679348306 :: 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 a6989586621679348344 a6989586621679348345 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM3Sym3 a6989586621679348375 a6989586621679348376 a6989586621679348377 :: 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 a6989586621679965820 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym2 a6989586621679965851 a6989586621679965852 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym2 a6989586621679965937 a6989586621679965938 :: 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 a6989586621679965878 a6989586621679965879 a6989586621679965880 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904 :: TyFun [d] [e] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip5Sym4 a6989586621679965998 a6989586621679965999 a6989586621679966000 a6989586621679966001 :: TyFun [e] [(a, b, c, d, e)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: 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 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple5Sym4 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun e (a, b, c, d, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftM5Sym2 a6989586621679348306 a6989586621679348307 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM4Sym3 a6989586621679348344 a6989586621679348345 a6989586621679348346 :: 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 a6989586621679965820 a6989586621679965821 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 :: TyFun [d] ([e] ~> [f]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftM5Sym3 a6989586621679348306 a6989586621679348307 a6989586621679348308 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

SuppressUnusedWarnings (LiftM4Sym4 a6989586621679348344 a6989586621679348345 a6989586621679348346 a6989586621679348347 :: 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 a6989586621679965820 a6989586621679965821 a6989586621679965822 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882 :: TyFun [e] [f] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (Tuple6Sym5 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun f (a, b, c, d, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftM5Sym4 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 :: 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 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 :: TyFun [e] ([f] ~> [g]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (LiftM5Sym5 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 a6989586621679348310 :: 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 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856 :: TyFun [f] [g] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (Tuple7Sym6 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun g (a, b, c, d, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

SuppressUnusedWarnings (ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 :: TyFun [f] ([g] ~> [h]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

SuppressUnusedWarnings (ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826 :: TyFun [g] [h] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TyCon f :: k1 ~> k5) (x :: k1) 
Instance details

Defined in Data.Singletons

type Apply (TyCon f :: k1 ~> k5) (x :: k1) = ApplyTyCon f @@ x
type Apply DivSym0 (a6989586621679566965 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply DivSym0 (a6989586621679566965 :: Natural) = DivSym1 a6989586621679566965
type Apply ModSym0 (a6989586621679567401 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply ModSym0 (a6989586621679567401 :: Natural) = ModSym1 a6989586621679567401
type Apply QuotSym0 (a6989586621679568006 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply QuotSym0 (a6989586621679568006 :: Natural) = QuotSym1 a6989586621679568006
type Apply RemSym0 (a6989586621679567995 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

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

Defined in GHC.TypeLits.Singletons.Internal

type Apply (^@#@$) (a6989586621679556329 :: Natural) = (^@#@$$) a6989586621679556329
type Apply DivModSym0 (a6989586621679568024 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply DivModSym0 (a6989586621679568024 :: Natural) = DivModSym1 a6989586621679568024
type Apply QuotRemSym0 (a6989586621679568017 :: Natural) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply QuotRemSym0 (a6989586621679568017 :: Natural) = QuotRemSym1 a6989586621679568017
type Apply ShowParenSym0 (a6989586621680208653 :: Bool) Source # 
Instance details

Defined in Text.Show.Singletons

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

Defined in Data.Bool.Singletons

type Apply (&&@#@$) (a6989586621679132115 :: Bool) = (&&@#@$$) a6989586621679132115
type Apply (||@#@$) (a6989586621679132472 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

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

Defined in GHC.TypeLits.Singletons

type Apply ConsSymbolSym0 (a6989586621679569296 :: Char) = ConsSymbolSym1 a6989586621679569296
type Apply ShowCharSym0 (a6989586621680208680 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621680208680 :: Char) = ShowCharSym1 a6989586621680208680
type Apply ShowStringSym0 (a6989586621680208669 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621680208669 :: Symbol) = ShowStringSym1 a6989586621680208669
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) (a6989586621681120576 :: Natural) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Text.Show.Singletons

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

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679814681 :: Natural) = ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type
type Apply (UnlessSym0 :: TyFun Bool (f () ~> f ()) -> Type) (a6989586621681205232 :: Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

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

Defined in Control.Monad.Singletons.Internal

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

Defined in Data.Bool.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.Maybe.Singletons

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.Singletons.Base.Instances

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

Defined in Text.Show.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Bool.Singletons

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Eq.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in GHC.Base.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in GHC.Num.Singletons

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

Defined in Data.Eq.Singletons

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

Defined in GHC.TypeLits.Singletons.Internal

type Apply ((<=?@#@$) :: TyFun k (k ~> Bool) -> Type) (a6989586621679556760 :: k) = (<=?@#@$$) a6989586621679556760
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) (a6989586621681205242 :: Natural) Source # 
Instance details

Defined in Control.Monad.Singletons

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

Defined in Control.Monad.Singletons

type Apply (ReplicateMSym0 :: TyFun Natural (m a ~> m [a]) -> Type) (a6989586621681205260 :: Natural) = ReplicateMSym1 a6989586621681205260 :: TyFun (m a) (m [a]) -> Type
type Apply ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) (a6989586621679327005 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply ((&@#@$) :: TyFun a ((a ~> b) ~> b) -> Type) (a6989586621679327005 :: a) = (&@#@$$) a6989586621679327005 :: TyFun (a ~> b) b -> Type
type Apply (Bool_Sym1 a6989586621679130897 :: TyFun a (Bool ~> a) -> Type) (a6989586621679130898 :: a) Source # 
Instance details

Defined in Data.Bool.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym1 a6989586621679815152 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815153 :: a) = DeleteBySym2 a6989586621679815152 a6989586621679815153
type Apply (InsertBySym1 a6989586621679815110 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815111 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym1 a6989586621679815110 :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679815111 :: a) = InsertBySym2 a6989586621679815110 a6989586621679815111
type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) = ShowsPrecSym2 a6989586621680208714 a6989586621680208715
type Apply (EnumFromThenToSym1 a6989586621679612942 :: TyFun a (a ~> [a]) -> Type) (a6989586621679612943 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679612942 :: TyFun a (a ~> [a]) -> Type) (a6989586621679612943 :: a) = EnumFromThenToSym2 a6989586621679612942 a6989586621679612943
type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680862528 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in GHC.Base.Singletons

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

Defined in GHC.Base.Singletons

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

Defined in Data.Proxy.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680390186 :: a) = NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type
type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679577734 :: b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679577734 :: b) = Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type
type Apply (IfSym1 a6989586621679133031 :: TyFun k (k ~> k) -> Type) (a6989586621679133032 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym1 a6989586621679133031 :: TyFun k (k ~> k) -> Type) (a6989586621679133032 :: k) = IfSym2 a6989586621679133031 a6989586621679133032
type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679046760 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

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

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) (a6989586621679348489 :: a) = (<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type
type Apply (ScanlSym1 a6989586621681120649 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120650 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym1 a6989586621681120649 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120650 :: b) = ScanlSym2 a6989586621681120649 a6989586621681120650
type Apply (ScanrSym1 a6989586621681120637 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120638 :: b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym1 a6989586621681120637 :: TyFun b ([a] ~> NonEmpty b) -> Type) (a6989586621681120638 :: b) = ScanrSym2 a6989586621681120637 a6989586621681120638
type Apply (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815592 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815592 :: b) = ScanlSym2 a6989586621679815591 a6989586621679815592
type Apply (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815565 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815565 :: b) = ScanrSym2 a6989586621679815564 a6989586621679815565
type Apply (ComparingSym1 a6989586621679237099 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679237100 :: b) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym1 a6989586621679237099 :: TyFun b (b ~> Ordering) -> Type) (a6989586621679237100 :: b) = ComparingSym2 a6989586621679237099 a6989586621679237100
type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679046809 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679046809 :: a) = Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type
type Apply (CurrySym1 a6989586621679172893 :: TyFun a (b ~> c) -> Type) (a6989586621679172894 :: a) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym1 a6989586621679172893 :: TyFun a (b ~> c) -> Type) (a6989586621679172894 :: a) = CurrySym2 a6989586621679172893 a6989586621679172894
type Apply (FlipSym1 a6989586621679180195 :: TyFun b (a ~> c) -> Type) (a6989586621679180196 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679180195 :: TyFun b (a ~> c) -> Type) (a6989586621679180196 :: b) = FlipSym2 a6989586621679180195 a6989586621679180196
type Apply (Tuple3Sym1 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679046761 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym1 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679046761 :: b) = Tuple3Sym2 a6989586621679046760 a6989586621679046761 :: TyFun c (a, b, c) -> Type
type Apply (Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type) (a6989586621680390415 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type) (a6989586621680390415 :: b) = Foldl'Sym2 a6989586621680390414 a6989586621680390415 :: TyFun (t a) b -> Type
type Apply (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) (a6989586621680390408 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) (a6989586621680390408 :: b) = FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type
type Apply (Foldr'Sym1 a6989586621680390400 :: TyFun b (t a ~> b) -> Type) (a6989586621680390401 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym1 a6989586621680390400 :: TyFun b (t a ~> b) -> Type) (a6989586621680390401 :: b) = Foldr'Sym2 a6989586621680390400 a6989586621680390401 :: TyFun (t a) b -> Type
type Apply (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) (a6989586621680390394 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) (a6989586621680390394 :: b) = FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type
type Apply (OnSym2 a6989586621679327018 a6989586621679327019 :: TyFun a (a ~> c) -> Type) (a6989586621679327020 :: a) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym2 a6989586621679327018 a6989586621679327019 :: TyFun a (a ~> c) -> Type) (a6989586621679327020 :: a) = OnSym3 a6989586621679327018 a6989586621679327019 a6989586621679327020
type Apply (Tuple5Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (a, b, c, d, e))))) -> Type) (a6989586621679046878 :: 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) (a6989586621679046878 :: a) = Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type
type Apply (MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741279 :: a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741279 :: a) = MapAccumLSym2 a6989586621680741278 a6989586621680741279 :: TyFun (t b) (a, t c) -> Type
type Apply (MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741269 :: a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type) (a6989586621680741269 :: a) = MapAccumRSym2 a6989586621680741268 a6989586621680741269 :: TyFun (t b) (a, t c) -> Type
type Apply (Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679046810 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679046810 :: b) = Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type
type Apply (FoldlMSym1 a6989586621680390349 :: TyFun b (t a ~> m b) -> Type) (a6989586621680390350 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym1 a6989586621680390349 :: TyFun b (t a ~> m b) -> Type) (a6989586621680390350 :: b) = FoldlMSym2 a6989586621680390349 a6989586621680390350 :: TyFun (t a) (m b) -> Type
type Apply (FoldrMSym1 a6989586621680390367 :: TyFun b (t a ~> m b) -> Type) (a6989586621680390368 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym1 a6989586621680390367 :: TyFun b (t a ~> m b) -> Type) (a6989586621680390368 :: b) = FoldrMSym2 a6989586621680390367 a6989586621680390368 :: TyFun (t a) (m b) -> Type
type Apply (Tuple6Sym0 :: TyFun a (b ~> (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f)))))) -> Type) (a6989586621679046969 :: 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) (a6989586621679046969 :: a) = Tuple6Sym1 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type
type Apply (Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679046879 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679046879 :: b) = Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type
type Apply (Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679046811 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679046811 :: c) = Tuple4Sym3 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: 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) (a6989586621679047084 :: 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) (a6989586621679047084 :: a) = Tuple7Sym1 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type
type Apply (Tuple6Sym1 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679046970 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym1 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679046970 :: b) = Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type
type Apply (Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679046880 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679046880 :: c) = Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type
type Apply (Tuple7Sym1 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679047085 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym1 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679047085 :: b) = Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type
type Apply (Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679046971 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679046971 :: c) = Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type
type Apply (Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679046881 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679046881 :: d) = Tuple5Sym4 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun e (a, b, c, d, e) -> Type
type Apply (Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679047086 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679047086 :: c) = Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type
type Apply (Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679046972 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679046972 :: d) = Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type
type Apply (Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679047087 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679047087 :: d) = Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type
type Apply (Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679046973 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679046973 :: e) = Tuple6Sym5 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun f (a, b, c, d, e, f) -> Type
type Apply (Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679047088 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679047088 :: e) = Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type
type Apply (Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679047089 :: f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679047089 :: f) = Tuple7Sym6 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun g (a, b, c, d, e, f, g) -> Type
type Apply ((<**>@#@$$) a6989586621679348472 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679348473 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<**>@#@$$) a6989586621679348472 :: TyFun (f (a ~> b)) (f b) -> Type) (a6989586621679348473 :: f (a ~> b)) = a6989586621679348472 <**> a6989586621679348473
type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621681120384 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply ((!!@#@$) :: TyFun (NonEmpty a) (Natural ~> a) -> Type) (a6989586621681120384 :: NonEmpty a) = (!!@#@$$) a6989586621681120384
type Apply ((:$$:@#@$) :: TyFun (ErrorMessage' s) (ErrorMessage' s ~> ErrorMessage' s) -> Type) (a6989586621680205232 :: ErrorMessage' s) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

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

Defined in Data.Singletons.Base.TypeError

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

Defined in Data.List.NonEmpty.Singletons

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

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

Defined in GHC.Base.Singletons

type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679180230 :: [a]) = (++@#@$$) a6989586621679180230
type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208723 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208723 :: [a]) = ShowListSym1 a6989586621680208723
type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621681120375 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipSym0 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty (a, b)) -> Type) (a6989586621681120375 :: NonEmpty a) = ZipSym1 a6989586621681120375 :: TyFun (NonEmpty b) (NonEmpty (a, b)) -> Type
type Apply (DeleteFirstsBySym1 a6989586621679815142 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679815143 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym1 a6989586621679815142 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679815143 :: [a]) = DeleteFirstsBySym2 a6989586621679815142 a6989586621679815143
type Apply (IntersectBySym1 a6989586621679814967 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814968 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym1 a6989586621679814967 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814968 :: [a]) = IntersectBySym2 a6989586621679814967 a6989586621679814968
type Apply (UnionBySym1 a6989586621679814606 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814607 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym1 a6989586621679814606 :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679814607 :: [a]) = UnionBySym2 a6989586621679814606 a6989586621679814607
type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679815371 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679815371 :: [a]) = ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type
type Apply (ShowListWithSym1 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208689 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym1 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208689 :: [a]) = ShowListWithSym2 a6989586621680208688 a6989586621680208689
type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679815359 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679815359 :: [a]) = Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type
type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679348512 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) (a6989586621679348512 :: f (a ~> b)) = (<*>@#@$$) a6989586621679348512
type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679532908 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$) :: TyFun (f a) ((a ~> b) ~> f b) -> Type) (a6989586621679532908 :: f a) = (<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type
type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679532901 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply (($>@#@$) :: TyFun (f a) (b ~> f b) -> Type) (a6989586621679532901 :: f a) = ($>@#@$$) a6989586621679532901 :: TyFun b (f b) -> Type
type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679348472 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<**>@#@$) :: TyFun (f a) (f (a ~> b) ~> f b) -> Type) (a6989586621679348472 :: f a) = (<**>@#@$$) a6989586621679348472 :: TyFun (f (a ~> b)) (f b) -> Type
type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679348633 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<|>@#@$) :: TyFun (f a) (f a ~> f a) -> Type) (a6989586621679348633 :: f a) = (<|>@#@$$) a6989586621679348633
type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679348287 :: m (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ApSym0 :: TyFun (m (a ~> b)) (m a ~> m b) -> Type) (a6989586621679348287 :: m (a ~> b)) = ApSym1 a6989586621679348287
type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679348592 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) (a6989586621679348592 :: m a) = (>>=@#@$$) a6989586621679348592 :: TyFun (a ~> m b) (m b) -> Type
type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679348639 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (MplusSym0 :: TyFun (m a) (m a ~> m a) -> Type) (a6989586621679348639 :: m a) = MplusSym1 a6989586621679348639
type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621681083531 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipSym0 :: TyFun (m a) (m b ~> m (a, b)) -> Type) (a6989586621681083531 :: m a) = MzipSym1 a6989586621681083531 :: TyFun (m b) (m (a, b)) -> Type
type Apply (ZipWithSym1 a6989586621681120364 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681120365 :: NonEmpty a) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ZipWithSym1 a6989586621681120364 :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty c) -> Type) (a6989586621681120365 :: NonEmpty a) = ZipWithSym2 a6989586621681120364 a6989586621681120365
type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679966021 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [(a, b, c, d)]))) -> Type) (a6989586621679966021 :: [a]) = Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type
type Apply (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679815348 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679815348 :: [a]) = ZipWithSym2 a6989586621679815347 a6989586621679815348
type Apply (Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679815360 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679815360 :: [b]) = Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type
type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679348529 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) (a6989586621679348529 :: f a) = (<*@#@$$) a6989586621679348529 :: TyFun (f b) (f a) -> Type
type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679348524 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) (a6989586621679348524 :: f a) = (*>@#@$$) a6989586621679348524 :: TyFun (f b) (f b) -> Type
type Apply (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) (x :: f a) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Apply (PairSym0 :: TyFun (f a) (g a ~> Product f g a) -> Type) (x :: f a) = PairSym1 x :: TyFun (g a) (Product f g a) -> Type
type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679348597 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) (a6989586621679348597 :: m a) = (>>@#@$$) a6989586621679348597 :: TyFun (m b) (m b) -> Type
type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621680390332 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621680390332 :: t a) = For_Sym1 a6989586621680390332 :: TyFun (a ~> f b) (f ()) -> Type
type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680741302 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForSym0 :: TyFun (t a) ((a ~> f b) ~> f (t b)) -> Type) (a6989586621680741302 :: t a) = ForSym1 a6989586621680741302 :: TyFun (a ~> f b) (f (t b)) -> Type
type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621680390312 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621680390312 :: t a) = ForM_Sym1 a6989586621680390312 :: TyFun (a ~> m b) (m ()) -> Type
type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680741291 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForMSym0 :: TyFun (t a) ((a ~> m b) ~> m (t b)) -> Type) (a6989586621680741291 :: t a) = ForMSym1 a6989586621680741291 :: TyFun (a ~> m b) (m (t b)) -> Type
type Apply (Zip5Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)])))) -> Type) (a6989586621679965998 :: [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) (a6989586621679965998 :: [a]) = Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type
type Apply (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679815333 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679815333 :: [a]) = ZipWith3Sym2 a6989586621679815332 a6989586621679815333
type Apply (ZipWithM_Sym1 a6989586621681205305 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621681205306 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithM_Sym1 a6989586621681205305 :: TyFun [a] ([b] ~> m ()) -> Type) (a6989586621681205306 :: [a]) = ZipWithM_Sym2 a6989586621681205305 a6989586621681205306
type Apply (ZipWithMSym1 a6989586621681205315 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621681205316 :: [a]) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (ZipWithMSym1 a6989586621681205315 :: TyFun [a] ([b] ~> m [c]) -> Type) (a6989586621681205316 :: [a]) = ZipWithMSym2 a6989586621681205315 a6989586621681205316
type Apply (Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679966022 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym1 a6989586621679966021 :: TyFun [b] ([c] ~> ([d] ~> [(a, b, c, d)])) -> Type) (a6989586621679966022 :: [b]) = Zip4Sym2 a6989586621679966021 a6989586621679966022 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type
type Apply (LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679348519 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679348519 :: f a) = LiftA2Sym2 a6989586621679348518 a6989586621679348519
type Apply (MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621681083538 :: m a) Source # 
Instance details

Defined in Control.Monad.Zip.Singletons

type Apply (MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type) (a6989586621681083538 :: m a) = MzipWithSym2 a6989586621681083537 a6989586621681083538
type Apply (LiftM2Sym1 a6989586621679348399 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679348400 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM2Sym1 a6989586621679348399 :: TyFun (m a1) (m a2 ~> m r) -> Type) (a6989586621679348400 :: m a1) = LiftM2Sym2 a6989586621679348399 a6989586621679348400
type Apply (Zip6Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))))) -> Type) (a6989586621679965970 :: [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) (a6989586621679965970 :: [a]) = Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type
type Apply (ZipWith4Sym1 a6989586621679965901 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679965902 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym1 a6989586621679965901 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> [e]))) -> Type) (a6989586621679965902 :: [a]) = ZipWith4Sym2 a6989586621679965901 a6989586621679965902
type Apply (Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679965999 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym1 a6989586621679965998 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [(a, b, c, d, e)]))) -> Type) (a6989586621679965999 :: [b]) = Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type
type Apply (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679815334 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679815334 :: [b]) = ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334
type Apply (Zip4Sym2 a6989586621679966021 a6989586621679966022 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679966023 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip4Sym2 a6989586621679966021 a6989586621679966022 :: TyFun [c] ([d] ~> [(a, b, c, d)]) -> Type) (a6989586621679966023 :: [c]) = Zip4Sym3 a6989586621679966021 a6989586621679966022 a6989586621679966023 :: TyFun [d] [(a, b, c, d)] -> Type
type Apply (LiftA3Sym1 a6989586621679348450 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679348451 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym1 a6989586621679348450 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type) (a6989586621679348451 :: f a) = LiftA3Sym2 a6989586621679348450 a6989586621679348451
type Apply (LiftM3Sym1 a6989586621679348375 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679348376 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym1 a6989586621679348375 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type) (a6989586621679348376 :: m a1) = LiftM3Sym2 a6989586621679348375 a6989586621679348376
type Apply (Zip7Sym0 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))))) -> Type) (a6989586621679965937 :: [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) (a6989586621679965937 :: [a]) = Zip7Sym1 a6989586621679965937 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type
type Apply (ZipWith5Sym1 a6989586621679965878 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679965879 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym1 a6989586621679965878 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f])))) -> Type) (a6989586621679965879 :: [a]) = ZipWith5Sym2 a6989586621679965878 a6989586621679965879
type Apply (Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679965971 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym1 a6989586621679965970 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)])))) -> Type) (a6989586621679965971 :: [b]) = Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type
type Apply (ZipWith4Sym2 a6989586621679965901 a6989586621679965902 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679965903 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym2 a6989586621679965901 a6989586621679965902 :: TyFun [b] ([c] ~> ([d] ~> [e])) -> Type) (a6989586621679965903 :: [b]) = ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903
type Apply (Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679966000 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym2 a6989586621679965998 a6989586621679965999 :: TyFun [c] ([d] ~> ([e] ~> [(a, b, c, d, e)])) -> Type) (a6989586621679966000 :: [c]) = Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type
type Apply (LiftA3Sym2 a6989586621679348450 a6989586621679348451 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679348452 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA3Sym2 a6989586621679348450 a6989586621679348451 :: TyFun (f b) (f c ~> f d) -> Type) (a6989586621679348452 :: f b) = LiftA3Sym3 a6989586621679348450 a6989586621679348451 a6989586621679348452
type Apply (LiftM4Sym1 a6989586621679348344 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679348345 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym1 a6989586621679348344 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> m r))) -> Type) (a6989586621679348345 :: m a1) = LiftM4Sym2 a6989586621679348344 a6989586621679348345
type Apply (LiftM3Sym2 a6989586621679348375 a6989586621679348376 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679348377 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM3Sym2 a6989586621679348375 a6989586621679348376 :: TyFun (m a2) (m a3 ~> m r) -> Type) (a6989586621679348377 :: m a2) = LiftM3Sym3 a6989586621679348375 a6989586621679348376 a6989586621679348377
type Apply (ZipWith6Sym1 a6989586621679965851 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679965852 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym1 a6989586621679965851 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g]))))) -> Type) (a6989586621679965852 :: [a]) = ZipWith6Sym2 a6989586621679965851 a6989586621679965852
type Apply (Zip7Sym1 a6989586621679965937 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679965938 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym1 a6989586621679965937 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))))) -> Type) (a6989586621679965938 :: [b]) = Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type
type Apply (ZipWith5Sym2 a6989586621679965878 a6989586621679965879 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679965880 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym2 a6989586621679965878 a6989586621679965879 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> [f]))) -> Type) (a6989586621679965880 :: [b]) = ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880
type Apply (Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679965972 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym2 a6989586621679965970 a6989586621679965971 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [(a, b, c, d, e, f)]))) -> Type) (a6989586621679965972 :: [c]) = Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type
type Apply (ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679965904 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith4Sym3 a6989586621679965901 a6989586621679965902 a6989586621679965903 :: TyFun [c] ([d] ~> [e]) -> Type) (a6989586621679965904 :: [c]) = ZipWith4Sym4 a6989586621679965901 a6989586621679965902 a6989586621679965903 a6989586621679965904
type Apply (Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679966001 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip5Sym3 a6989586621679965998 a6989586621679965999 a6989586621679966000 :: TyFun [d] ([e] ~> [(a, b, c, d, e)]) -> Type) (a6989586621679966001 :: [d]) = Zip5Sym4 a6989586621679965998 a6989586621679965999 a6989586621679966000 a6989586621679966001 :: TyFun [e] [(a, b, c, d, e)] -> Type
type Apply (LiftM5Sym1 a6989586621679348306 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679348307 :: m a1) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym1 a6989586621679348306 :: TyFun (m a1) (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r)))) -> Type) (a6989586621679348307 :: m a1) = LiftM5Sym2 a6989586621679348306 a6989586621679348307
type Apply (LiftM4Sym2 a6989586621679348344 a6989586621679348345 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679348346 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym2 a6989586621679348344 a6989586621679348345 :: TyFun (m a2) (m a3 ~> (m a4 ~> m r)) -> Type) (a6989586621679348346 :: m a2) = LiftM4Sym3 a6989586621679348344 a6989586621679348345 a6989586621679348346
type Apply (ZipWith7Sym1 a6989586621679965820 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679965821 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym1 a6989586621679965820 :: TyFun [a] ([b] ~> ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))))) -> Type) (a6989586621679965821 :: [a]) = ZipWith7Sym2 a6989586621679965820 a6989586621679965821
type Apply (ZipWith6Sym2 a6989586621679965851 a6989586621679965852 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679965853 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym2 a6989586621679965851 a6989586621679965852 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> [g])))) -> Type) (a6989586621679965853 :: [b]) = ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853
type Apply (Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679965939 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym2 a6989586621679965937 a6989586621679965938 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])))) -> Type) (a6989586621679965939 :: [c]) = Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type
type Apply (ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679965881 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym3 a6989586621679965878 a6989586621679965879 a6989586621679965880 :: TyFun [c] ([d] ~> ([e] ~> [f])) -> Type) (a6989586621679965881 :: [c]) = ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881
type Apply (Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679965973 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym3 a6989586621679965970 a6989586621679965971 a6989586621679965972 :: TyFun [d] ([e] ~> ([f] ~> [(a, b, c, d, e, f)])) -> Type) (a6989586621679965973 :: [d]) = Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type
type Apply (LiftM5Sym2 a6989586621679348306 a6989586621679348307 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679348308 :: m a2) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym2 a6989586621679348306 a6989586621679348307 :: TyFun (m a2) (m a3 ~> (m a4 ~> (m a5 ~> m r))) -> Type) (a6989586621679348308 :: m a2) = LiftM5Sym3 a6989586621679348306 a6989586621679348307 a6989586621679348308
type Apply (LiftM4Sym3 a6989586621679348344 a6989586621679348345 a6989586621679348346 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679348347 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM4Sym3 a6989586621679348344 a6989586621679348345 a6989586621679348346 :: TyFun (m a3) (m a4 ~> m r) -> Type) (a6989586621679348347 :: m a3) = LiftM4Sym4 a6989586621679348344 a6989586621679348345 a6989586621679348346 a6989586621679348347
type Apply (ZipWith7Sym2 a6989586621679965820 a6989586621679965821 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679965822 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym2 a6989586621679965820 a6989586621679965821 :: TyFun [b] ([c] ~> ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h]))))) -> Type) (a6989586621679965822 :: [b]) = ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822
type Apply (ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679965854 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym3 a6989586621679965851 a6989586621679965852 a6989586621679965853 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> [g]))) -> Type) (a6989586621679965854 :: [c]) = ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854
type Apply (Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679965940 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym3 a6989586621679965937 a6989586621679965938 a6989586621679965939 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)]))) -> Type) (a6989586621679965940 :: [d]) = Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type
type Apply (ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679965882 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith5Sym4 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 :: TyFun [d] ([e] ~> [f]) -> Type) (a6989586621679965882 :: [d]) = ZipWith5Sym5 a6989586621679965878 a6989586621679965879 a6989586621679965880 a6989586621679965881 a6989586621679965882
type Apply (Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679965974 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip6Sym4 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 :: TyFun [e] ([f] ~> [(a, b, c, d, e, f)]) -> Type) (a6989586621679965974 :: [e]) = Zip6Sym5 a6989586621679965970 a6989586621679965971 a6989586621679965972 a6989586621679965973 a6989586621679965974 :: TyFun [f] [(a, b, c, d, e, f)] -> Type
type Apply (LiftM5Sym3 a6989586621679348306 a6989586621679348307 a6989586621679348308 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679348309 :: m a3) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym3 a6989586621679348306 a6989586621679348307 a6989586621679348308 :: TyFun (m a3) (m a4 ~> (m a5 ~> m r)) -> Type) (a6989586621679348309 :: m a3) = LiftM5Sym4 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309
type Apply (ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679965823 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym3 a6989586621679965820 a6989586621679965821 a6989586621679965822 :: TyFun [c] ([d] ~> ([e] ~> ([f] ~> ([g] ~> [h])))) -> Type) (a6989586621679965823 :: [c]) = ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823
type Apply (ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679965855 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym4 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 :: TyFun [d] ([e] ~> ([f] ~> [g])) -> Type) (a6989586621679965855 :: [d]) = ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855
type Apply (Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679965941 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym4 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 :: TyFun [e] ([f] ~> ([g] ~> [(a, b, c, d, e, f, g)])) -> Type) (a6989586621679965941 :: [e]) = Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type
type Apply (LiftM5Sym4 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679348310 :: m a4) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftM5Sym4 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 :: TyFun (m a4) (m a5 ~> m r) -> Type) (a6989586621679348310 :: m a4) = LiftM5Sym5 a6989586621679348306 a6989586621679348307 a6989586621679348308 a6989586621679348309 a6989586621679348310
type Apply (ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679965824 :: [d]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym4 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 :: TyFun [d] ([e] ~> ([f] ~> ([g] ~> [h]))) -> Type) (a6989586621679965824 :: [d]) = ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824
type Apply (ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679965856 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith6Sym5 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 :: TyFun [e] ([f] ~> [g]) -> Type) (a6989586621679965856 :: [e]) = ZipWith6Sym6 a6989586621679965851 a6989586621679965852 a6989586621679965853 a6989586621679965854 a6989586621679965855 a6989586621679965856
type Apply (Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679965942 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip7Sym5 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 :: TyFun [f] ([g] ~> [(a, b, c, d, e, f, g)]) -> Type) (a6989586621679965942 :: [f]) = Zip7Sym6 a6989586621679965937 a6989586621679965938 a6989586621679965939 a6989586621679965940 a6989586621679965941 a6989586621679965942 :: TyFun [g] [(a, b, c, d, e, f, g)] -> Type
type Apply (ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679965825 :: [e]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym5 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 :: TyFun [e] ([f] ~> ([g] ~> [h])) -> Type) (a6989586621679965825 :: [e]) = ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825
type Apply (ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679965826 :: [f]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith7Sym6 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 :: TyFun [f] ([g] ~> [h]) -> Type) (a6989586621679965826 :: [f]) = ZipWith7Sym7 a6989586621679965820 a6989586621679965821 a6989586621679965822 a6989586621679965823 a6989586621679965824 a6989586621679965825 a6989586621679965826
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 ((&@#@$$) a6989586621679327005 :: TyFun (a ~> b) b -> Type) (a6989586621679327006 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply ((&@#@$$) a6989586621679327005 :: TyFun (a ~> b) b -> Type) (a6989586621679327006 :: a ~> b) = a6989586621679327005 & a6989586621679327006
type Apply ((<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679532909 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<&>@#@$$) a6989586621679532908 :: TyFun (a ~> b) (f b) -> Type) (a6989586621679532909 :: a ~> b) = a6989586621679532908 <&> a6989586621679532909
type Apply ((>>=@#@$$) a6989586621679348592 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679348593 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$$) a6989586621679348592 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679348593 :: a ~> m b) = a6989586621679348592 >>= a6989586621679348593
type Apply (For_Sym1 a6989586621680390332 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680390333 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym1 a6989586621680390332 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680390333 :: a ~> f b) = For_ a6989586621680390332 a6989586621680390333
type Apply (ForSym1 a6989586621680741302 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680741303 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForSym1 a6989586621680741302 :: TyFun (a ~> f b) (f (t b)) -> Type) (a6989586621680741303 :: a ~> f b) = For a6989586621680741302 a6989586621680741303
type Apply (ForM_Sym1 a6989586621680390312 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680390313 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym1 a6989586621680390312 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680390313 :: a ~> m b) = ForM_ a6989586621680390312 a6989586621680390313
type Apply (ForMSym1 a6989586621680741291 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680741292 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (ForMSym1 a6989586621680741291 :: TyFun (a ~> m b) (m (t b)) -> Type) (a6989586621680741292 :: a ~> m b) = ForM a6989586621680741291 a6989586621680741292
type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621680208653 a6989586621680208654
type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) = ShowListWithSym1 a6989586621680208688
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120308 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120308 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621681120308
type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679815130 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SortBySym0 :: TyFun (a ~> (a ~> Ordering)) ([a] ~> [a]) -> Type) (a6989586621679815130 :: a ~> (a ~> Ordering)) = SortBySym1 a6989586621679815130
type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815110 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InsertBySym0 :: TyFun (a ~> (a ~> Ordering)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815110 :: a ~> (a ~> Ordering)) = InsertBySym1 a6989586621679815110
type Apply (GroupBy1Sym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120430 :: 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) (a6989586621681120430 :: a ~> (a ~> Bool)) = GroupBy1Sym1 a6989586621681120430
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120321 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120321 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621681120321
type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679815142 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteFirstsBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679815142 :: a ~> (a ~> Bool)) = DeleteFirstsBySym1 a6989586621679815142
type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814967 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (IntersectBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814967 :: a ~> (a ~> Bool)) = IntersectBySym1 a6989586621679814967
type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814606 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnionBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> ([a] ~> [a])) -> Type) (a6989586621679814606 :: a ~> (a ~> Bool)) = UnionBySym1 a6989586621679814606
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120482 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120482 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621681120482
type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679814759 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (GroupBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [[a]]) -> Type) (a6989586621679814759 :: a ~> (a ~> Bool)) = GroupBySym1 a6989586621679814759
type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679814626 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (NubBySym0 :: TyFun (a ~> (a ~> Bool)) ([a] ~> [a]) -> Type) (a6989586621679814626 :: a ~> (a ~> Bool)) = NubBySym1 a6989586621679814626
type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815152 :: a ~> (a ~> Bool)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DeleteBySym0 :: TyFun (a ~> (a ~> Bool)) (a ~> ([a] ~> [a])) -> Type) (a6989586621679815152 :: a ~> (a ~> Bool)) = DeleteBySym1 a6989586621679815152
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120626 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120626 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621681120626
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120618 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120618 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621681120618
type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815582 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815582 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679815582
type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815544 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815544 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679815544
type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679815658 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Foldl1'Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) (a6989586621679815658 :: a ~> (a ~> a)) = Foldl1'Sym1 a6989586621679815658
type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120540 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (BreakSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120540 :: a ~> Bool) = BreakSym1 a6989586621681120540
type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120522 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (PartitionSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120522 :: a ~> Bool) = PartitionSym1 a6989586621681120522
type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120549 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SpanSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> ([a], [a])) -> Type) (a6989586621681120549 :: a ~> Bool) = SpanSym1 a6989586621681120549
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120558 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120558 :: a ~> Bool) = DropWhileSym1 a6989586621681120558
type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120531 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (FilterSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120531 :: a ~> Bool) = FilterSym1 a6989586621681120531
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120567 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) (NonEmpty a ~> [a]) -> Type) (a6989586621681120567 :: a ~> Bool) = TakeWhileSym1 a6989586621681120567
type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679180149 :: a ~> Bool) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679180149 :: a ~> Bool) = UntilSym1 a6989586621679180149
type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679815019 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndexSym0 :: TyFun (a ~> Bool) ([a] ~> Maybe Natural) -> Type) (a6989586621679815019 :: a ~> Bool) = FindIndexSym1 a6989586621679815019
type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814849 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814849 :: a ~> Bool) = BreakSym1 a6989586621679814849
type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814737 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (PartitionSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814737 :: a ~> Bool) = PartitionSym1 a6989586621679814737
type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814884 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814884 :: a ~> Bool) = SpanSym1 a6989586621679814884
type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679814996 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FindIndicesSym0 :: TyFun (a ~> Bool) ([a] ~> [Natural]) -> Type) (a6989586621679814996 :: a ~> Bool) = FindIndicesSym1 a6989586621679814996
type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814921 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814921 :: a ~> Bool) = DropWhileEndSym1 a6989586621679814921
type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814938 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814938 :: a ~> Bool) = DropWhileSym1 a6989586621679814938
type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679815053 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679815053 :: a ~> Bool) = FilterSym1 a6989586621679815053
type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814953 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814953 :: a ~> Bool) = TakeWhileSym1 a6989586621679814953
type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390215 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390215 :: a ~> (a ~> Ordering)) = MaximumBySym1 a6989586621680390215 :: TyFun (t a) a -> Type
type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390195 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680390195 :: a ~> (a ~> Ordering)) = MinimumBySym1 a6989586621680390195 :: TyFun (t a) a -> Type
type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390425 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390425 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type
type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390420 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390420 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120637 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120637 :: a ~> (b ~> b)) = ScanrSym1 a6989586621681120637
type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815564 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815564 :: a ~> (b ~> b)) = ScanrSym1 a6989586621679815564
type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679579760 :: a ~> Maybe b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (MapMaybeSym0 :: TyFun (a ~> Maybe b) ([a] ~> [b]) -> Type) (a6989586621679579760 :: a ~> Maybe b) = MapMaybeSym1 a6989586621679579760
type Apply (UnfoldSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681120784 :: 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) (a6989586621681120784 :: a ~> (b, Maybe a)) = UnfoldSym1 a6989586621681120784
type Apply (UnfoldrSym0 :: TyFun (a ~> (b, Maybe a)) (a ~> NonEmpty b) -> Type) (a6989586621681120749 :: 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) (a6989586621681120749 :: a ~> (b, Maybe a)) = UnfoldrSym1 a6989586621681120749
type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621681205203 :: a ~> Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (MfilterSym0 :: TyFun (a ~> Bool) (m a ~> m a) -> Type) (a6989586621681205203 :: a ~> Bool) = MfilterSym1 a6989586621681205203 :: TyFun (m a) (m a) -> Type
type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680390168 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680390168 :: a ~> Bool) = FindSym1 a6989586621680390168 :: TyFun (t a) (Maybe a) -> Type
type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390235 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390235 :: a ~> Bool) = AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type
type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390244 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390244 :: a ~> Bool) = AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type
type Apply (UntilSym1 a6989586621679180149 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679180150 :: a ~> a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym1 a6989586621679180149 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679180150 :: a ~> a) = UntilSym2 a6989586621679180149 a6989586621679180150
type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120414 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120414 :: a ~> b) = GroupAllWith1Sym1 a6989586621681120414
type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120423 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWith1Sym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty (NonEmpty a)) -> Type) (a6989586621681120423 :: a ~> b) = GroupWith1Sym1 a6989586621681120423
type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621681120679 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) (a6989586621681120679 :: a ~> b) = MapSym1 a6989586621681120679
type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120464 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupAllWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120464 :: a ~> b) = GroupAllWithSym1 a6989586621681120464
type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120473 :: a ~> b) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (GroupWithSym0 :: TyFun (a ~> b) ([a] ~> [NonEmpty a]) -> Type) (a6989586621681120473 :: a ~> b) = GroupWithSym1 a6989586621681120473
type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679180239 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679180239 :: a ~> b) = MapSym1 a6989586621679180239
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) (a6989586621679180167 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679180167 :: a ~> b) = ($!@#@$$) a6989586621679180167
type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679180176 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) (a6989586621679180176 :: a ~> b) = ($@#@$$) a6989586621679180176
type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621681205365 :: a ~> m Bool) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply (FilterMSym0 :: TyFun (a ~> m Bool) ([a] ~> m [a]) -> Type) (a6989586621681205365 :: a ~> m Bool) = FilterMSym1 a6989586621681205365
type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120299 :: a ~> o) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (SortWithSym0 :: TyFun (a ~> o) (NonEmpty a ~> NonEmpty a) -> Type) (a6989586621681120299 :: a ~> o) = SortWithSym1 a6989586621681120299
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120649 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.NonEmpty.Singletons

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> NonEmpty b)) -> Type) (a6989586621681120649 :: b ~> (a ~> b)) = ScanlSym1 a6989586621681120649
type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815591 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815591 :: b ~> (a ~> b)) = ScanlSym1 a6989586621679815591
type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679815436 :: b ~> Maybe (a, b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnfoldrSym0 :: TyFun (b ~> Maybe (a, b)) (b ~> [a]) -> Type) (a6989586621679815436 :: b ~> Maybe (a, b)) = UnfoldrSym1 a6989586621679815436
type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679237099 :: b ~> a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (ComparingSym0 :: TyFun (b ~> a) (b ~> (b ~> Ordering)) -> Type) (a6989586621679237099 :: b ~> a) = ComparingSym1 a6989586621679237099
type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679172893 :: (a, b) ~> c) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679172893 :: (a, b) ~> c) = CurrySym1 a6989586621679172893
type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390400 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390400 :: a ~> (b ~> b)) = Foldr'Sym1 a6989586621680390400 :: TyFun b (t a ~> b) -> Type
type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390393 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390393 :: a ~> (b ~> b)) = FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) (a6989586621681120364 :: 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) (a6989586621681120364 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621681120364
type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679172885 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679172885 :: a ~> (b ~> c)) = UncurrySym1 a6989586621679172885
type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679815347 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679815347 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621679815347
type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679180195 :: a ~> (b ~> c)) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679180195 :: a ~> (b ~> c)) = FlipSym1 a6989586621679180195
type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680390263 :: a ~> [b]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680390263 :: a ~> [b]) = ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type
type Apply (Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679577735 :: a ~> b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679577735 :: a ~> b) = Maybe_Sym2 a6989586621679577734 a6989586621679577735
type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348484 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348484 :: a ~> b) = FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type
type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348461 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftASym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348461 :: a ~> b) = LiftASym1 a6989586621679348461 :: TyFun (f a) (f b) -> Type
type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679532919 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679532919 :: a ~> b) = (<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type
type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621681205219 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<$!>@#@$) :: TyFun (a ~> b) (m a ~> m b) -> Type) (a6989586621681205219 :: a ~> b) = (<$!>@#@$$) a6989586621681205219 :: TyFun (m a) (m b) -> Type
type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680741254 :: a ~> b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FmapDefaultSym0 :: TyFun (a ~> b) (t a ~> t b) -> Type) (a6989586621680741254 :: a ~> b) = FmapDefaultSym1 a6989586621680741254 :: TyFun (t a) (t b) -> Type
type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679334944 :: a ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679334944 :: a ~> c) = Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type
type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680390387 :: a ~> m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680390387 :: a ~> m) = FoldMapSym1 a6989586621680390387 :: TyFun (t a) m -> Type
type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680741235 :: a ~> m) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (FoldMapDefaultSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680741235 :: a ~> m) = FoldMapDefaultSym1 a6989586621680741235 :: TyFun (t a) m -> Type
type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679348437 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) (a6989586621679348437 :: a ~> m b) = (=<<@#@$$) a6989586621679348437
type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679348416 :: a1 ~> r) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftMSym0 :: TyFun (a1 ~> r) (m a1 ~> m r) -> Type) (a6989586621679348416 :: a1 ~> r) = LiftMSym1 a6989586621679348416 :: TyFun (m a1) (m r) -> Type
type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390414 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390414 :: b ~> (a ~> b)) = Foldl'Sym1 a6989586621680390414 :: TyFun b (t a ~> b) -> Type
type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390407 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390407 :: b ~> (a ~> b)) = FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type
type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679327018 :: b ~> (b ~> c)) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym0 :: TyFun (b ~> (b ~> c)) ((a ~> b) ~> (a ~> (a ~> c))) -> Type) (a6989586621679327018 :: b ~> (b ~> c)) = OnSym1 a6989586621679327018 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type
type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679180207 :: b ~> c) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) (a6989586621679180207 :: b ~> c) = (.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type
type Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) (a6989586621679815332 :: 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) (a6989586621679815332 :: a ~> (b ~> (c ~> d))) = ZipWith3Sym1 a6989586621679815332
type Apply (MapAccumLSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680741278 :: 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) (a6989586621680741278 :: a ~> (b ~> (a, c))) = MapAccumLSym1 a6989586621680741278 :: TyFun a (t b ~> (a, t c)) -> Type
type Apply (MapAccumRSym0 :: TyFun (a ~> (b ~> (a, c))) (a ~> (t b ~> (a, t c))) -> Type) (a6989586621680741268 :: 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) (a6989586621680741268 :: a ~> (b ~> (a, c))) = MapAccumRSym1 a6989586621680741268 :: TyFun a (t b ~> (a, t c)) -> Type
type Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) (a6989586621679348518 :: 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) (a6989586621679348518 :: a ~> (b ~> c)) = LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type
type Apply (MzipWithSym0 :: TyFun (a ~> (b ~> c)) (m a ~> (m b ~> m c)) -> Type) (a6989586621681083537 :: 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) (a6989586621681083537 :: a ~> (b ~> c)) = MzipWithSym1 a6989586621681083537 :: TyFun (m a) (m b ~> m c) -> Type
type Apply (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621680390367 :: 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) (a6989586621680390367 :: a ~> (b ~> m b)) = FoldrMSym1 a6989586621680390367 :: TyFun b (t a ~> m b) -> Type
type Apply (ZipWithM_Sym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m ())) -> Type) (a6989586621681205305 :: 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) (a6989586621681205305 :: a ~> (b ~> m c)) = ZipWithM_Sym1 a6989586621681205305
type Apply (ZipWithMSym0 :: TyFun (a ~> (b ~> m c)) ([a] ~> ([b] ~> m [c])) -> Type) (a6989586621681205315 :: 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) (a6989586621681205315 :: a ~> (b ~> m c)) = ZipWithMSym1 a6989586621681205315
type Apply (OnSym1 a6989586621679327018 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679327019 :: a ~> b) Source # 
Instance details

Defined in Data.Function.Singletons

type Apply (OnSym1 a6989586621679327018 :: TyFun (a ~> b) (a ~> (a ~> c)) -> Type) (a6989586621679327019 :: a ~> b) = OnSym2 a6989586621679327018 a6989586621679327019
type Apply ((.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679180208 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679180208 :: a ~> b) = a6989586621679180207 .@#@$$$ a6989586621679180208
type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621680390341 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621680390341 :: a ~> f b) = Traverse_Sym1 a6989586621680390341 :: TyFun (t a) (f ()) -> Type
type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680733986 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680733986 :: a ~> f b) = TraverseSym1 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type
type Apply (MapAndUnzipMSym0 :: TyFun (a ~> m (b, c)) ([a] ~> m ([b], [c])) -> Type) (a6989586621681205324 :: 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) (a6989586621681205324 :: a ~> m (b, c)) = MapAndUnzipMSym1 a6989586621681205324
type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621681205350 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((>=>@#@$) :: TyFun (a ~> m b) ((b ~> m c) ~> (a ~> m c)) -> Type) (a6989586621681205350 :: a ~> m b) = (>=>@#@$$) a6989586621681205350 :: TyFun (b ~> m c) (a ~> m c) -> Type
type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621680390321 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621680390321 :: a ~> m b) = MapM_Sym1 a6989586621680390321 :: TyFun (t a) (m ()) -> Type
type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680733994 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680733994 :: a ~> m b) = MapMSym1 a6989586621680733994 :: TyFun (t a) (m (t b)) -> Type
type Apply (LiftM2Sym0 :: TyFun (a1 ~> (a2 ~> r)) (m a1 ~> (m a2 ~> m r)) -> Type) (a6989586621679348399 :: 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) (a6989586621679348399 :: a1 ~> (a2 ~> r)) = LiftM2Sym1 a6989586621679348399 :: TyFun (m a1) (m a2 ~> m r) -> Type
type Apply (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621680390349 :: 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) (a6989586621680390349 :: b ~> (a ~> m b)) = FoldlMSym1 a6989586621680390349 :: TyFun b (t a ~> m b) -> Type
type Apply (Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679334945 :: b ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679334945 :: b ~> c) = Either_Sym2 a6989586621679334944 a6989586621679334945
type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621681205338 :: b ~> m c) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<=<@#@$) :: TyFun (b ~> m c) ((a ~> m b) ~> (a ~> m c)) -> Type) (a6989586621681205338 :: b ~> m c) = (<=<@#@$$) a6989586621681205338 :: TyFun (a ~> m b) (a ~> m c) -> Type
type Apply (ZipWith4Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> e)))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> [e])))) -> Type) (a6989586621679965901 :: 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) (a6989586621679965901 :: a ~> (b ~> (c ~> (d ~> e)))) = ZipWith4Sym1 a6989586621679965901
type Apply (LiftA3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) (f a ~> (f b ~> (f c ~> f d))) -> Type) (a6989586621679348450 :: 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) (a6989586621679348450 :: a ~> (b ~> (c ~> d))) = LiftA3Sym1 a6989586621679348450 :: TyFun (f a) (f b ~> (f c ~> f d)) -> Type
type Apply ((<=<@#@$$) a6989586621681205338 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621681205339 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((<=<@#@$$) a6989586621681205338 :: TyFun (a ~> m b) (a ~> m c) -> Type) (a6989586621681205339 :: a ~> m b) = a6989586621681205338 <=<@#@$$$ a6989586621681205339
type Apply (LiftM3Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> r))) (m a1 ~> (m a2 ~> (m a3 ~> m r))) -> Type) (a6989586621679348375 :: 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) (a6989586621679348375 :: a1 ~> (a2 ~> (a3 ~> r))) = LiftM3Sym1 a6989586621679348375 :: TyFun (m a1) (m a2 ~> (m a3 ~> m r)) -> Type
type Apply ((>=>@#@$$) a6989586621681205350 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621681205351 :: b ~> m c) Source # 
Instance details

Defined in Control.Monad.Singletons

type Apply ((>=>@#@$$) a6989586621681205350 :: TyFun (b ~> m c) (a ~> m c) -> Type) (a6989586621681205351 :: b ~> m c) = a6989586621681205350 >=>@#@$$$ a6989586621681205351
type Apply (ZipWith5Sym0 :: TyFun (a ~> (b ~> (c ~> (d ~> (e ~> f))))) ([a] ~> ([b] ~> ([c] ~> ([d] ~> ([e] ~> [f]))))) -> Type) (a6989586621679965878 :: 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) (a6989586621679965878 :: a ~> (b ~> (c ~> (d ~> (e ~> f))))) = ZipWith5Sym1 a6989586621679965878
type Apply (LiftM4Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> m r)))) -> Type) (a6989586621679348344 :: 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) (a6989586621679348344 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> r)))) = LiftM4Sym1 a6989586621679348344 :: 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) (a6989586621679965851 :: 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) (a6989586621679965851 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> g)))))) = ZipWith6Sym1 a6989586621679965851
type Apply (LiftM5Sym0 :: TyFun (a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) (m a1 ~> (m a2 ~> (m a3 ~> (m a4 ~> (m a5 ~> m r))))) -> Type) (a6989586621679348306 :: 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) (a6989586621679348306 :: a1 ~> (a2 ~> (a3 ~> (a4 ~> (a5 ~> r))))) = LiftM5Sym1 a6989586621679348306 :: 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) (a6989586621679965820 :: 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) (a6989586621679965820 :: a ~> (b ~> (c ~> (d ~> (e ~> (f ~> (g ~> h))))))) = ZipWith7Sym1 a6989586621679965820

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 (Apply (Apply (Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) 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 (Apply (Apply (Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) 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.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.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.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.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.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
IsString Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Methods

fromString :: String -> Symbol #

Monoid Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons

Semigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SingKind Symbol

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Symbol 
Instance details

Defined in GHC.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 (Apply (Apply ((==@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) 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 (MemptySym0 :: Symbol) Source #

sMappend :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun Symbol (Symbol ~> Symbol) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Symbol]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Symbol] Symbol -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun Symbol (Symbol ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun Symbol (Symbol ~> Symbol) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun Symbol (Symbol ~> Symbol) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty Symbol). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Symbol) Symbol -> Type) 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 (Apply (FromStringSym0 :: TyFun Symbol Symbol -> Type) t) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Symbol ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Symbol). Sing t -> Sing (Apply (Show_Sym0 :: TyFun Symbol Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Symbol]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Symbol] (Symbol ~> Symbol) -> Type) t1) t2) Source #

TestCoercion SSymbol

Since: base-4.18.0.0

Instance details

Defined in GHC.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.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.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 a6989586621680208653 :: 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 a6989586621679569296 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

SuppressUnusedWarnings (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowStringSym1 a6989586621680208669 :: 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 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsPrecSym1 a6989586621680208714 :: 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 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type DemoteRep Symbol 
Instance details

Defined in GHC.Generics

type DemoteRep Symbol = String
data Sing (s :: Symbol) 
Instance details

Defined in GHC.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 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 (a6989586621679566100 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply KnownSymbolSym0 (a6989586621679566100 :: Symbol) = KnownSymbol a6989586621679566100
type Apply ShowCommaSpaceSym0 (a6989586621680208635 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCommaSpaceSym0 (a6989586621680208635 :: Symbol) = ShowCommaSpace a6989586621680208635
type Apply ShowSpaceSym0 (a6989586621680208641 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowSpaceSym0 (a6989586621680208641 :: Symbol) = ShowSpace a6989586621680208641
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 k2 -> Type) (a6989586621680205235 :: PErrorMessage) Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Apply (TypeErrorSym0 :: TyFun PErrorMessage k2 -> Type) (a6989586621680205235 :: PErrorMessage) = TypeError a6989586621680205235 :: k2
type Apply (ConsSymbolSym1 a6989586621679569296 :: TyFun Symbol Symbol -> Type) (a6989586621679569297 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply (ConsSymbolSym1 a6989586621679569296 :: TyFun Symbol Symbol -> Type) (a6989586621679569297 :: Symbol) = ConsSymbol a6989586621679569296 a6989586621679569297
type Apply (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) (a6989586621680208681 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) (a6989586621680208681 :: Symbol) = ShowChar a6989586621680208680 a6989586621680208681
type Apply (ShowStringSym1 a6989586621680208669 :: TyFun Symbol Symbol -> Type) (a6989586621680208670 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621680208669 :: TyFun Symbol Symbol -> Type) (a6989586621680208670 :: Symbol) = ShowString a6989586621680208669 a6989586621680208670
type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (a6989586621681179965 :: Symbol) Source # 
Instance details

Defined in Data.String.Singletons

type Apply (FromStringSym0 :: TyFun Symbol k2 -> Type) (a6989586621681179965 :: Symbol) = FromString a6989586621681179965 :: k2
type Apply (ErrorSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555664 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555664 :: Symbol) = Error a6989586621679555664 :: k2
type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555924 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555924 :: Symbol) = ErrorWithoutStackTrace a6989586621679555924 :: k2
type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621680208719 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621680208719 :: a) = Show_ a6989586621680208719
type Apply (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) (a6989586621680208724 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) (a6989586621680208724 :: Symbol) = ShowList a6989586621680208723 a6989586621680208724
type Apply (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) (a6989586621680208655 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) (a6989586621680208655 :: Symbol) = ShowParen a6989586621680208653 a6989586621680208654 a6989586621680208655
type Apply (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) (a6989586621680208707 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) (a6989586621680208707 :: Symbol) = Shows a6989586621680208706 a6989586621680208707
type Apply (ShowListWithSym2 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) (a6989586621680208690 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym2 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) (a6989586621680208690 :: Symbol) = ShowListWith a6989586621680208688 a6989586621680208689 a6989586621680208690
type Apply (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) (a6989586621680208716 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) (a6989586621680208716 :: Symbol) = ShowsPrec a6989586621680208714 a6989586621680208715 a6989586621680208716
type Apply UnconsSymbolSym0 (a6989586621679569801 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply UnconsSymbolSym0 (a6989586621679569801 :: Symbol) = UnconsSymbol a6989586621679569801
type Apply ShowParenSym0 (a6989586621680208653 :: Bool) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowParenSym0 (a6989586621680208653 :: Bool) = ShowParenSym1 a6989586621680208653
type Apply ConsSymbolSym0 (a6989586621679569296 :: Char) Source # 
Instance details

Defined in GHC.TypeLits.Singletons

type Apply ConsSymbolSym0 (a6989586621679569296 :: Char) = ConsSymbolSym1 a6989586621679569296
type Apply ShowCharSym0 (a6989586621680208680 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621680208680 :: Char) = ShowCharSym1 a6989586621680208680
type Apply ShowStringSym0 (a6989586621680208669 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621680208669 :: Symbol) = ShowStringSym1 a6989586621680208669
type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208714 :: Natural) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208714 :: Natural) = ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type
type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208706 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208706 :: a) = ShowsSym1 a6989586621680208706
type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) = ShowsPrecSym2 a6989586621680208714 a6989586621680208715
type Apply UnlinesSym0 (a6989586621679815198 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

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

Defined in Data.List.Singletons.Internal

type Apply UnwordsSym0 (a6989586621679815188 :: [Symbol]) = Unwords a6989586621679815188
type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208723 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208723 :: [a]) = ShowListSym1 a6989586621680208723
type Apply (ShowListWithSym1 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208689 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym1 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208689 :: [a]) = ShowListWithSym2 a6989586621680208688 a6989586621680208689
type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621680208653 a6989586621680208654
type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) = ShowListWithSym1 a6989586621680208688

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 (Apply (FstSym0 :: TyFun (a, b) a -> Type) 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 (Apply (SndSym0 :: TyFun (a, b) b -> Type) 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 (Apply (Apply (Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) 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 (Apply (Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) 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) = Apply (Apply (TFHelper_6989586621679137938Sym0 :: TyFun a (a ~> Bool) -> Type) arg) arg1

type (arg :: a) /= (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) /= (arg1 :: a) = Apply (Apply (TFHelper_6989586621679137927Sym0 :: TyFun a (a ~> Bool) -> Type) arg) arg1

Instances

Instances details
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 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 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 (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 (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 (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 (NonEmpty a) Source # 
Instance details

Defined in Data.Eq.Singletons

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 (Either a b) Source # 
Instance details

Defined in Data.Eq.Singletons

PEq (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

PEq (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.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 (Apply (Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) infix 4 Source #

default (%==) :: forall (t1 :: a) (t2 :: a). Apply (Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679137938Sym0 :: TyFun a (a ~> Bool) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) infix 4 Source #

default (%/=) :: forall (t1 :: a) (t2 :: a). Apply (Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679137927Sym0 :: TyFun a (a ~> Bool) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) Source #

Instances

Instances details
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 (Apply (Apply ((==@#@$) :: TyFun All (All ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun All (All ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun Any (Any ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun Any (Any ~> Bool) -> Type) t1) t2) Source #

SEq Void Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((==@#@$) :: TyFun Void (Void ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun Void (Void ~> Bool) -> Type) t1) t2) Source #

SEq Ordering Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((==@#@$) :: TyFun Ordering (Ordering ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun Ordering (Ordering ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) t1) t2) Source #

SEq () Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((==@#@$) :: TyFun () (() ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun () (() ~> Bool) -> Type) t1) t2) Source #

SEq Bool Source # 
Instance details

Defined in Data.Eq.Singletons

Methods

(%==) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((==@#@$) :: TyFun Bool (Bool ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun Bool (Bool ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun Char (Char ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun Char (Char ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Identity a) (Identity a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Identity a) (Identity a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Down a) (Down a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Down a) (Down a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Max a) (Max a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Max a) (Max a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Min a) (Min a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Min a) (Min a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Dual a) (Dual a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Dual a) (Dual a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Product a) (Product a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Product a) (Product a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Sum a) (Sum a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Sum a) (Sum a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (TYPE rep) (TYPE rep ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: TYPE rep) (t2 :: TYPE rep). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (TYPE rep) (TYPE rep ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun [a] ([a] ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Either a b) (Either a b ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Either a b) (Either a b ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (a, b) ((a, b) ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (a, b) ((a, b) ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Const a b) (Const a b ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Const a b) (Const a b ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Product f g a) (Product f g a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Product f g a) (Product f g a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Sum f g a) (Sum f g a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Sum f g a) (Sum f g a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (Compose f g a) (Compose f g a ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (Compose f g a) (Compose f g a ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) t1) t2) Source #

(%/=) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((/=@#@$) :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) 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 (Apply (Apply ((==@#@$) :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) 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 (Apply (Apply ((/=@#@$) :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) t1) t2) Source #

class POrd a Source #

Associated Types

type Compare (arg :: a) (arg1 :: a) :: Ordering Source #

type Compare (arg :: a) (arg1 :: a) = Apply (Apply (Compare_6989586621679237142Sym0 :: TyFun a (a ~> Ordering) -> Type) arg) arg1

type (arg :: a) < (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) < (arg1 :: a) = Apply (Apply (TFHelper_6989586621679237163Sym0 :: TyFun a (a ~> Bool) -> Type) arg) arg1

type (arg :: a) <= (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) <= (arg1 :: a) = Apply (Apply (TFHelper_6989586621679237179Sym0 :: TyFun a (a ~> Bool) -> Type) arg) arg1

type (arg :: a) > (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) > (arg1 :: a) = Apply (Apply (TFHelper_6989586621679237195Sym0 :: TyFun a (a ~> Bool) -> Type) arg) arg1

type (arg :: a) >= (arg1 :: a) :: Bool infix 4 Source #

type (arg :: a) >= (arg1 :: a) = Apply (Apply (TFHelper_6989586621679237211Sym0 :: TyFun a (a ~> Bool) -> Type) arg) arg1

type Max (arg :: a) (arg1 :: a) :: a Source #

type Max (arg :: a) (arg1 :: a) = Apply (Apply (Max_6989586621679237227Sym0 :: TyFun a (a ~> a) -> Type) arg) arg1

type Min (arg :: a) (arg1 :: a) :: a Source #

type Min (arg :: a) (arg1 :: a) = Apply (Apply (Min_6989586621679237243Sym0 :: TyFun a (a ~> a) -> Type) arg) arg1

Instances

Instances details
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 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 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 (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 (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 (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 (NonEmpty a) Source # 
Instance details

Defined in Data.Ord.Singletons

POrd (Maybe a) Source # 
Instance details

Defined in Data.Ord.Singletons

POrd [a] Source # 
Instance details

Defined in Data.Ord.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 (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.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 (Apply (Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) t1) t2) Source #

default sCompare :: forall (t1 :: a) (t2 :: a). Apply (Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) t1) t2 ~ Apply (Apply (Compare_6989586621679237142Sym0 :: TyFun a (a ~> Ordering) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) infix 4 Source #

default (%<) :: forall (t1 :: a) (t2 :: a). Apply (Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679237163Sym0 :: TyFun a (a ~> Bool) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) infix 4 Source #

default (%<=) :: forall (t1 :: a) (t2 :: a). Apply (Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679237179Sym0 :: TyFun a (a ~> Bool) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) infix 4 Source #

default (%>) :: forall (t1 :: a) (t2 :: a). Apply (Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679237195Sym0 :: TyFun a (a ~> Bool) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) infix 4 Source #

default (%>=) :: forall (t1 :: a) (t2 :: a). Apply (Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679237211Sym0 :: TyFun a (a ~> Bool) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) t1) t2) Source #

default sMax :: forall (t1 :: a) (t2 :: a). Apply (Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) t1) t2 ~ Apply (Apply (Max_6989586621679237227Sym0 :: TyFun a (a ~> a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun a (a ~> a) -> Type) t1) t2) Source #

default sMin :: forall (t1 :: a) (t2 :: a). Apply (Apply (MinSym0 :: TyFun a (a ~> a) -> Type) t1) t2 ~ Apply (Apply (Min_6989586621679237243Sym0 :: TyFun a (a ~> a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun a (a ~> a) -> Type) t1) t2) Source #

Instances

Instances details
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 (Apply (Apply (CompareSym0 :: TyFun All (All ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun All (All ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun All (All ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun All (All ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun All (All ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun All (All ~> All) -> Type) t1) t2) Source #

sMin :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun All (All ~> All) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun Any (Any ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun Any (Any ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun Any (Any ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun Any (Any ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun Any (Any ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun Any (Any ~> Any) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun Any (Any ~> Any) -> Type) t1) t2) Source #

SOrd Void Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply (CompareSym0 :: TyFun Void (Void ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun Void (Void ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun Void (Void ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun Void (Void ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun Void (Void ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun Void (Void ~> Void) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun Void (Void ~> Void) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun Ordering (Ordering ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun Ordering (Ordering ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun Ordering (Ordering ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun Ordering (Ordering ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun Ordering (Ordering ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun Ordering (Ordering ~> Ordering) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun Ordering (Ordering ~> Ordering) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun Natural (Natural ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun Natural (Natural ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun Natural (Natural ~> Natural) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun Natural (Natural ~> Natural) -> Type) t1) t2) Source #

SOrd () Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

sCompare :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply (CompareSym0 :: TyFun () (() ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun () (() ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun () (() ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun () (() ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun () (() ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun () (() ~> ()) -> Type) t1) t2) Source #

sMin :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun () (() ~> ()) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun Bool (Bool ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun Bool (Bool ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun Bool (Bool ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun Bool (Bool ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun Bool (Bool ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun Bool (Bool ~> Bool) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun Bool (Bool ~> Bool) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun Char (Char ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun Char (Char ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun Char (Char ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun Char (Char ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun Char (Char ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun Char (Char ~> Char) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun Char (Char ~> Char) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun Symbol (Symbol ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun Symbol (Symbol ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun Symbol (Symbol ~> Symbol) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun Symbol (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Identity a) (Identity a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Identity a) (Identity a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Identity a) (Identity a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Identity a) (Identity a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Identity a) (Identity a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Identity a) (Identity a ~> Identity a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Identity a) (Identity a ~> Identity a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (First a) (First a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (First a) (First a ~> First a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Last a) (Last a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Last a) (Last a ~> Last a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Down a) (Down a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Down a) (Down a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Down a) (Down a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Down a) (Down a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Down a) (Down a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Down a) (Down a ~> Down a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Down a) (Down a ~> Down a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (First a) (First a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (First a) (First a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (First a) (First a ~> First a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Last a) (Last a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Last a) (Last a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Last a) (Last a ~> Last a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Max a) (Max a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Max a) (Max a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Max a) (Max a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Max a) (Max a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Max a) (Max a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Max a) (Max a ~> Max a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Max a) (Max a ~> Max a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Min a) (Min a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Min a) (Min a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Min a) (Min a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Min a) (Min a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Min a) (Min a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Min a) (Min a ~> Min a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Min a) (Min a ~> Min a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> WrappedMonoid m) -> Type) t1) t2) Source #

sMin :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> WrappedMonoid m) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Dual a) (Dual a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Dual a) (Dual a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Dual a) (Dual a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Dual a) (Dual a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Dual a) (Dual a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Dual a) (Dual a ~> Dual a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Dual a) (Dual a ~> Dual a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Product a) (Product a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Product a) (Product a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Product a) (Product a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Product a) (Product a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Product a) (Product a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Product a) (Product a ~> Product a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Product a) (Product a ~> Product a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Sum a) (Sum a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Sum a) (Sum a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Sum a) (Sum a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Sum a) (Sum a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Sum a) (Sum a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Sum a) (Sum a ~> Sum a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Sum a) (Sum a ~> Sum a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (NonEmpty a) (NonEmpty a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> NonEmpty a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: NonEmpty a) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> NonEmpty a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Maybe a) (Maybe a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Maybe a) (Maybe a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun [a] ([a] ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun [a] ([a] ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2) Source #

sMin :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun [a] ([a] ~> [a]) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Either a b) (Either a b ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Either a b) (Either a b ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Either a b) (Either a b ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Either a b) (Either a b ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Either a b) (Either a b ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Either a b) (Either a b ~> Either a b) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Either a b) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Either a b) (Either a b ~> Either a b) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Proxy s) (Proxy s ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Proxy s) (Proxy s ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Arg a b) (Arg a b ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Arg a b) (Arg a b ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Arg a b) (Arg a b ~> Arg a b) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Arg a b) (Arg a b ~> Arg a b) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (a, b) ((a, b) ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (a, b) ((a, b) ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (a, b) ((a, b) ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (a, b) ((a, b) ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (a, b) ((a, b) ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (a, b) ((a, b) ~> (a, b)) -> Type) t1) t2) Source #

sMin :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (a, b) ((a, b) ~> (a, b)) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Const a b) (Const a b ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Const a b) (Const a b ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Const a b) (Const a b ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Const a b) (Const a b ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Const a b) (Const a b ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Const a b) (Const a b ~> Const a b) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Const a b) (Const a b ~> Const a b) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (a, b, c) ((a, b, c) ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (a, b, c) ((a, b, c) ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (a, b, c) ((a, b, c) ~> (a, b, c)) -> Type) t1) t2) Source #

sMin :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (a, b, c) ((a, b, c) ~> (a, b, c)) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Product f g a) (Product f g a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Product f g a) (Product f g a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Product f g a) (Product f g a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Product f g a) (Product f g a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Product f g a) (Product f g a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Product f g a) (Product f g a ~> Product f g a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Product f g a) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Product f g a) (Product f g a ~> Product f g a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Sum f g a) (Sum f g a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Sum f g a) (Sum f g a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Sum f g a) (Sum f g a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Sum f g a) (Sum f g a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Sum f g a) (Sum f g a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Sum f g a) (Sum f g a ~> Sum f g a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Sum f g a) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Sum f g a) (Sum f g a ~> Sum f g a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (a, b, c, d) ((a, b, c, d) ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (a, b, c, d) ((a, b, c, d) ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (a, b, c, d) ((a, b, c, d) ~> (a, b, c, d)) -> Type) t1) t2) Source #

sMin :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (a, b, c, d) ((a, b, c, d) ~> (a, b, c, d)) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (Compose f g a) (Compose f g a ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (Compose f g a) (Compose f g a ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (Compose f g a) (Compose f g a ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (Compose f g a) (Compose f g a ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (Compose f g a) (Compose f g a ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Compose f g a) (Compose f g a ~> Compose f g a) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Compose f g a) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Compose f g a) (Compose f g a ~> Compose f g a) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> (a, b, c, d, e)) -> Type) t1) t2) Source #

sMin :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> (a, b, c, d, e)) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Ordering) -> Type) t1) t2) Source #

(%<) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<@#@$) :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) t1) t2) Source #

(%<=) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<=@#@$) :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) t1) t2) Source #

(%>) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>@#@$) :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) t1) t2) Source #

(%>=) :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>=@#@$) :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> Bool) -> Type) t1) t2) Source #

sMax :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> (a, b, c, d, e, f)) -> Type) t1) t2) Source #

sMin :: forall (t1 :: (a, b, c, d, e, f)) (t2 :: (a, b, c, d, e, f)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (a, b, c, d, e, f) ((a, b, c, d, e, f) ~> (a, b, c, d, e, f)) -> Type) 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 (Apply (Apply (CompareSym0 :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Ordering) -> Type) 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 (Apply (Apply ((<@#@$) :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) 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 (Apply (Apply ((<=@#@$) :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) 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 (Apply (Apply ((>@#@$) :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) 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 (Apply (Apply ((>=@#@$) :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> Bool) -> Type) 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 (Apply (Apply (MaxSym0 :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> (a, b, c, d, e, f, g)) -> Type) 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 (Apply (Apply (MinSym0 :: TyFun (a, b, c, d, e, f, g) ((a, b, c, d, e, f, g) ~> (a, b, c, d, e, f, g)) -> Type) 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) = Apply (Apply (EnumFromTo_6989586621679612969Sym0 :: TyFun a (a ~> [a]) -> Type) arg) arg1

type EnumFromThenTo (arg :: a) (arg1 :: a) (arg2 :: a) :: [a] Source #

type EnumFromThenTo (arg :: a) (arg1 :: a) (arg2 :: a) = Apply (Apply (Apply (EnumFromThenTo_6989586621679612981Sym0 :: TyFun a (a ~> (a ~> [a])) -> Type) 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 (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

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 (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 (Apply (ToEnumSym0 :: TyFun Natural a -> Type) t) Source #

sFromEnum :: forall (t :: a). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun a Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) t1) t2) Source #

default sEnumFromTo :: forall (t1 :: a) (t2 :: a). Apply (Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) t1) t2 ~ Apply (Apply (EnumFromTo_6989586621679612969Sym0 :: TyFun a (a ~> [a]) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: a) (t2 :: a) (t3 :: a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) t1) t2) t3) Source #

default sEnumFromThenTo :: forall (t1 :: a) (t2 :: a) (t3 :: a). Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) t1) t2) t3 ~ Apply (Apply (Apply (EnumFromThenTo_6989586621679612981Sym0 :: TyFun a (a ~> (a ~> [a])) -> Type) t1) t2) t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) 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 (Apply (SuccSym0 :: TyFun Ordering Ordering -> Type) t) Source #

sPred :: forall (t :: Ordering). Sing t -> Sing (Apply (PredSym0 :: TyFun Ordering Ordering -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural Ordering -> Type) t) Source #

sFromEnum :: forall (t :: Ordering). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun Ordering Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun Ordering (Ordering ~> [Ordering]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Ordering) (t2 :: Ordering) (t3 :: Ordering). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun Ordering (Ordering ~> (Ordering ~> [Ordering])) -> Type) t1) t2) t3) Source #

SEnum Natural Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: Natural). Sing t -> Sing (Apply (SuccSym0 :: TyFun Natural Natural -> Type) t) Source #

sPred :: forall (t :: Natural). Sing t -> Sing (Apply (PredSym0 :: TyFun Natural Natural -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural Natural -> Type) t) Source #

sFromEnum :: forall (t :: Natural). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun Natural Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun Natural (Natural ~> [Natural]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Natural) (t2 :: Natural) (t3 :: Natural). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun Natural (Natural ~> (Natural ~> [Natural])) -> Type) t1) t2) t3) Source #

SEnum () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: ()). Sing t -> Sing (Apply (SuccSym0 :: TyFun () () -> Type) t) Source #

sPred :: forall (t :: ()). Sing t -> Sing (Apply (PredSym0 :: TyFun () () -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural () -> Type) t) Source #

sFromEnum :: forall (t :: ()). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun () Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun () (() ~> [()]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: ()) (t2 :: ()) (t3 :: ()). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun () (() ~> (() ~> [()])) -> Type) t1) t2) t3) Source #

SEnum Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: Bool). Sing t -> Sing (Apply (SuccSym0 :: TyFun Bool Bool -> Type) t) Source #

sPred :: forall (t :: Bool). Sing t -> Sing (Apply (PredSym0 :: TyFun Bool Bool -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural Bool -> Type) t) Source #

sFromEnum :: forall (t :: Bool). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun Bool Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun Bool (Bool ~> [Bool]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Bool) (t2 :: Bool) (t3 :: Bool). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun Bool (Bool ~> (Bool ~> [Bool])) -> Type) t1) t2) t3) Source #

SEnum Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sSucc :: forall (t :: Char). Sing t -> Sing (Apply (SuccSym0 :: TyFun Char Char -> Type) t) Source #

sPred :: forall (t :: Char). Sing t -> Sing (Apply (PredSym0 :: TyFun Char Char -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural Char -> Type) t) Source #

sFromEnum :: forall (t :: Char). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun Char Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun Char (Char ~> [Char]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Char) (t2 :: Char) (t3 :: Char). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun Char (Char ~> (Char ~> [Char])) -> Type) 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 (Apply (SuccSym0 :: TyFun (Identity a) (Identity a) -> Type) t) Source #

sPred :: forall (t :: Identity a). Sing t -> Sing (Apply (PredSym0 :: TyFun (Identity a) (Identity a) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (Identity a) -> Type) t) Source #

sFromEnum :: forall (t :: Identity a). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (Identity a) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (Identity a) (Identity a ~> [Identity a]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Identity a) (t2 :: Identity a) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Identity a) (Identity a ~> (Identity a ~> [Identity a])) -> Type) 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 (Apply (SuccSym0 :: TyFun (First a) (First a) -> Type) t) Source #

sPred :: forall (t :: First a). Sing t -> Sing (Apply (PredSym0 :: TyFun (First a) (First a) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (First a) -> Type) t) Source #

sFromEnum :: forall (t :: First a). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (First a) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (First a) (First a ~> [First a]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: First a) (t2 :: First a) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (First a) (First a ~> (First a ~> [First a])) -> Type) 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 (Apply (SuccSym0 :: TyFun (Last a) (Last a) -> Type) t) Source #

sPred :: forall (t :: Last a). Sing t -> Sing (Apply (PredSym0 :: TyFun (Last a) (Last a) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (Last a) -> Type) t) Source #

sFromEnum :: forall (t :: Last a). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (Last a) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (Last a) (Last a ~> [Last a]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Last a) (t2 :: Last a) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Last a) (Last a ~> (Last a ~> [Last a])) -> Type) 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 (Apply (SuccSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

sPred :: forall (t :: Max a). Sing t -> Sing (Apply (PredSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (Max a) -> Type) t) Source #

sFromEnum :: forall (t :: Max a). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (Max a) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (Max a) (Max a ~> [Max a]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Max a) (t2 :: Max a) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Max a) (Max a ~> (Max a ~> [Max a])) -> Type) 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 (Apply (SuccSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

sPred :: forall (t :: Min a). Sing t -> Sing (Apply (PredSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (Min a) -> Type) t) Source #

sFromEnum :: forall (t :: Min a). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (Min a) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (Min a) (Min a ~> [Min a]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Min a) (t2 :: Min a) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Min a) (Min a ~> (Min a ~> [Min a])) -> Type) 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 (Apply (SuccSym0 :: TyFun (WrappedMonoid a) (WrappedMonoid a) -> Type) t) Source #

sPred :: forall (t :: WrappedMonoid a). Sing t -> Sing (Apply (PredSym0 :: TyFun (WrappedMonoid a) (WrappedMonoid a) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (WrappedMonoid a) -> Type) t) Source #

sFromEnum :: forall (t :: WrappedMonoid a). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (WrappedMonoid a) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: WrappedMonoid a) (t2 :: WrappedMonoid a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (WrappedMonoid a) (WrappedMonoid a ~> [WrappedMonoid a]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: WrappedMonoid a) (t2 :: WrappedMonoid a) (t3 :: WrappedMonoid a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (WrappedMonoid a) (WrappedMonoid a ~> (WrappedMonoid a ~> [WrappedMonoid a])) -> Type) t1) t2) t3) Source #

SEnum (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sSucc :: forall (t :: Proxy s). Sing t -> Sing (Apply (SuccSym0 :: TyFun (Proxy s) (Proxy s) -> Type) t) Source #

sPred :: forall (t :: Proxy s). Sing t -> Sing (Apply (PredSym0 :: TyFun (Proxy s) (Proxy s) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (Proxy s) -> Type) t) Source #

sFromEnum :: forall (t :: Proxy s). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (Proxy s) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (Proxy s) (Proxy s ~> [Proxy s]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Proxy s) (t2 :: Proxy s) (t3 :: Proxy s). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Proxy s) (Proxy s ~> (Proxy s ~> [Proxy s])) -> Type) 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 (Apply (SuccSym0 :: TyFun (Const a b) (Const a b) -> Type) t) Source #

sPred :: forall (t :: Const a b). Sing t -> Sing (Apply (PredSym0 :: TyFun (Const a b) (Const a b) -> Type) t) Source #

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply (ToEnumSym0 :: TyFun Natural (Const a b) -> Type) t) Source #

sFromEnum :: forall (t :: Const a b). Sing t -> Sing (Apply (FromEnumSym0 :: TyFun (Const a b) Natural -> Type) t) Source #

sEnumFromTo :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (EnumFromToSym0 :: TyFun (Const a b) (Const a b ~> [Const a b]) -> Type) t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Const a b) (t2 :: Const a b) (t3 :: Const a b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Const a b) (Const a b ~> (Const a b ~> [Const a b])) -> Type) 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 (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 (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 (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 (Identity a) 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 (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 (MinBoundSym0 :: (a, b)) Source #

sMaxBound :: Sing (MaxBoundSym0 :: (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 (MinBoundSym0 :: (a, b, c)) Source #

sMaxBound :: Sing (MaxBoundSym0 :: (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 (MinBoundSym0 :: (a, b, c, d)) Source #

sMaxBound :: Sing (MaxBoundSym0 :: (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 (MinBoundSym0 :: (a, b, c, d, e)) Source #

sMaxBound :: Sing (MaxBoundSym0 :: (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 (MinBoundSym0 :: (a, b, c, d, e, f)) Source #

sMaxBound :: Sing (MaxBoundSym0 :: (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 (MinBoundSym0 :: (a, b, c, d, e, f, g)) Source #

sMaxBound :: Sing (MaxBoundSym0 :: (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) = Apply (Apply (TFHelper_6989586621679590968Sym0 :: TyFun a (a ~> a) -> Type) arg) arg1

type (arg :: a) * (arg1 :: a) :: a infixl 7 Source #

type Negate (arg :: a) :: a Source #

type Negate (arg :: a) = Apply (Negate_6989586621679590978Sym0 :: TyFun a a -> Type) 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 (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

PNum (Down a) Source # 
Instance details

Defined in GHC.Num.Singletons

PNum (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PNum (Min a) Source # 
Instance details

Defined in Data.Semigroup.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 (Apply (Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) t1) t2) infixl 6 Source #

(%-) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) t1) t2) infixl 6 Source #

default (%-) :: forall (t1 :: a) (t2 :: a). Apply (Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679590968Sym0 :: TyFun a (a ~> a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun a (a ~> a) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) t1) t2) infixl 7 Source #

sNegate :: forall (t :: a). Sing t -> Sing (Apply (NegateSym0 :: TyFun a a -> Type) t) Source #

default sNegate :: forall (t :: a). Apply (NegateSym0 :: TyFun a a -> Type) t ~ Apply (Negate_6989586621679590978Sym0 :: TyFun a a -> Type) t => Sing t -> Sing (Apply (NegateSym0 :: TyFun a a -> Type) t) Source #

sAbs :: forall (t :: a). Sing t -> Sing (Apply (AbsSym0 :: TyFun a a -> Type) t) Source #

sSignum :: forall (t :: a). Sing t -> Sing (Apply (SignumSym0 :: TyFun a a -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural a -> Type) t) 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 (Apply (Apply ((+@#@$) :: TyFun Natural (Natural ~> Natural) -> Type) t1) t2) Source #

(%-) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun Natural (Natural ~> Natural) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun Natural (Natural ~> Natural) -> Type) t1) t2) Source #

sNegate :: forall (t :: Natural). Sing t -> Sing (Apply (NegateSym0 :: TyFun Natural Natural -> Type) t) Source #

sAbs :: forall (t :: Natural). Sing t -> Sing (Apply (AbsSym0 :: TyFun Natural Natural -> Type) t) Source #

sSignum :: forall (t :: Natural). Sing t -> Sing (Apply (SignumSym0 :: TyFun Natural Natural -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural Natural -> Type) t) 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 (Apply (Apply ((+@#@$) :: TyFun (Identity a) (Identity a ~> Identity a) -> Type) t1) t2) Source #

(%-) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun (Identity a) (Identity a ~> Identity a) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun (Identity a) (Identity a ~> Identity a) -> Type) t1) t2) Source #

sNegate :: forall (t :: Identity a). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Identity a) (Identity a) -> Type) t) Source #

sAbs :: forall (t :: Identity a). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Identity a) (Identity a) -> Type) t) Source #

sSignum :: forall (t :: Identity a). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Identity a) (Identity a) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Identity a) -> Type) t) 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 (Apply (Apply ((+@#@$) :: TyFun (Down a) (Down a ~> Down a) -> Type) t1) t2) Source #

(%-) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun (Down a) (Down a ~> Down a) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun (Down a) (Down a ~> Down a) -> Type) t1) t2) Source #

sNegate :: forall (t :: Down a). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Down a) (Down a) -> Type) t) Source #

sAbs :: forall (t :: Down a). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Down a) (Down a) -> Type) t) Source #

sSignum :: forall (t :: Down a). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Down a) (Down a) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Down a) -> Type) t) 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 (Apply (Apply ((+@#@$) :: TyFun (Max a) (Max a ~> Max a) -> Type) t1) t2) Source #

(%-) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun (Max a) (Max a ~> Max a) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun (Max a) (Max a ~> Max a) -> Type) t1) t2) Source #

sNegate :: forall (t :: Max a). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

sAbs :: forall (t :: Max a). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

sSignum :: forall (t :: Max a). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Max a) -> Type) t) 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 (Apply (Apply ((+@#@$) :: TyFun (Min a) (Min a ~> Min a) -> Type) t1) t2) Source #

(%-) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun (Min a) (Min a ~> Min a) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun (Min a) (Min a ~> Min a) -> Type) t1) t2) Source #

sNegate :: forall (t :: Min a). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

sAbs :: forall (t :: Min a). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

sSignum :: forall (t :: Min a). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Min a) -> Type) t) 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 (Apply (Apply ((+@#@$) :: TyFun (Product a) (Product a ~> Product a) -> Type) t1) t2) Source #

(%-) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun (Product a) (Product a ~> Product a) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun (Product a) (Product a ~> Product a) -> Type) t1) t2) Source #

sNegate :: forall (t :: Product a). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Product a) (Product a) -> Type) t) Source #

sAbs :: forall (t :: Product a). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Product a) (Product a) -> Type) t) Source #

sSignum :: forall (t :: Product a). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Product a) (Product a) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Product a) -> Type) t) 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 (Apply (Apply ((+@#@$) :: TyFun (Sum a) (Sum a ~> Sum a) -> Type) t1) t2) Source #

(%-) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun (Sum a) (Sum a ~> Sum a) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun (Sum a) (Sum a ~> Sum a) -> Type) t1) t2) Source #

sNegate :: forall (t :: Sum a). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Sum a) (Sum a) -> Type) t) Source #

sAbs :: forall (t :: Sum a). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Sum a) (Sum a) -> Type) t) Source #

sSignum :: forall (t :: Sum a). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Sum a) (Sum a) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Sum a) -> Type) t) 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 (Apply (Apply ((+@#@$) :: TyFun (Const a b) (Const a b ~> Const a b) -> Type) t1) t2) Source #

(%-) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((-@#@$) :: TyFun (Const a b) (Const a b ~> Const a b) -> Type) t1) t2) Source #

(%*) :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*@#@$) :: TyFun (Const a b) (Const a b ~> Const a b) -> Type) t1) t2) Source #

sNegate :: forall (t :: Const a b). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Const a b) (Const a b) -> Type) t) Source #

sAbs :: forall (t :: Const a b). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Const a b) (Const a b) -> Type) t) Source #

sSignum :: forall (t :: Const a b). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Const a b) (Const a b) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Const a b) -> Type) t) 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 (Apply (Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) 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 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 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 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 (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 (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 (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 (NonEmpty a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

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 (Apply (Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) t1) t2) infixr 6 Source #

Instances

Instances details
SSemigroup All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(%<>) :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<>@#@$) :: TyFun All (All ~> All) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty All). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty All) All -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun Any (Any ~> Any) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty Any). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Any) Any -> Type) t) Source #

SSemigroup Void Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: Void) (t2 :: Void). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<>@#@$) :: TyFun Void (Void ~> Void) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty Void). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Void) Void -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun Ordering (Ordering ~> Ordering) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty Ordering). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Ordering) Ordering -> Type) t) Source #

SSemigroup () Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<>@#@$) :: TyFun () (() ~> ()) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty ()). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty ()) () -> Type) t) Source #

SSemigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

(%<>) :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty Symbol). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Symbol) Symbol -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Identity a) (Identity a ~> Identity a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Identity a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Identity a)) (Identity a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (First a)) (First a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Last a)) (Last a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Down a) (Down a ~> Down a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Down a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Down a)) (Down a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (First a)) (First a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Last a)) (Last a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Max a) (Max a ~> Max a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Max a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Max a)) (Max a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Min a) (Min a ~> Min a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Min a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Min a)) (Min a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (WrappedMonoid m) (WrappedMonoid m ~> WrappedMonoid m) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (WrappedMonoid m)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (WrappedMonoid m)) (WrappedMonoid m) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Dual a) (Dual a ~> Dual a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Dual a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Dual a)) (Dual a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Product a) (Product a ~> Product a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Product a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Product a)) (Product a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Sum a) (Sum a ~> Sum a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Sum a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Sum a)) (Sum a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (NonEmpty a) (NonEmpty a ~> NonEmpty a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Maybe a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Maybe a)) (Maybe a) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty [a]). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty [a]) [a] -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Either a b) (Either a b ~> Either a b) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Either a b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Either a b)) (Either a b) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Proxy s)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Proxy s)) (Proxy s) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (a ~> b) ((a ~> b) ~> (a ~> b)) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a ~> b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a ~> b)) (a ~> b) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (a, b) ((a, b) ~> (a, b)) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a, b)) (a, b) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (Const a b) (Const a b ~> Const a b) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Const a b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Const a b)) (Const a b) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (a, b, c) ((a, b, c) ~> (a, b, c)) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a, b, c)) (a, b, c) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (a, b, c, d) ((a, b, c, d) ~> (a, b, c, d)) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c, d)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a, b, c, d)) (a, b, c, d) -> Type) 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 (Apply (Apply ((<>@#@$) :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> (a, b, c, d, e)) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c, d, e)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a, b, c, d, e)) (a, b, c, d, e) -> Type) 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) = Apply (Apply (Mappend_6989586621680292333Sym0 :: TyFun a (a ~> a) -> Type) arg) arg1

type Mconcat (arg :: [a]) :: a Source #

type Mconcat (arg :: [a]) = Apply (Mconcat_6989586621680292347Sym0 :: TyFun [a] a -> Type) 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 (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 (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 (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 (MemptySym0 :: a) Source #

sMappend :: forall (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) t1) t2) Source #

default sMappend :: forall (t1 :: a) (t2 :: a). Apply (Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) t1) t2 ~ Apply (Apply (Mappend_6989586621680292333Sym0 :: TyFun a (a ~> a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [a] a -> Type) t) Source #

default sMconcat :: forall (t :: [a]). Apply (MconcatSym0 :: TyFun [a] a -> Type) t ~ Apply (Mconcat_6989586621680292347Sym0 :: TyFun [a] a -> Type) t => Sing t -> Sing (Apply (MconcatSym0 :: TyFun [a] a -> Type) t) Source #

Instances

Instances details
SMonoid All Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: All) Source #

sMappend :: forall (t1 :: All) (t2 :: All). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun All (All ~> All) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [All]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [All] All -> Type) t) Source #

SMonoid Any Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Any) Source #

sMappend :: forall (t1 :: Any) (t2 :: Any). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun Any (Any ~> Any) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Any]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Any] Any -> Type) t) Source #

SMonoid Ordering Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Ordering) Source #

sMappend :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun Ordering (Ordering ~> Ordering) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Ordering]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Ordering] Ordering -> Type) t) Source #

SMonoid () Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: ()) Source #

sMappend :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun () (() ~> ()) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [()]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [()] () -> Type) t) Source #

SMonoid Symbol Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Symbol) Source #

sMappend :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun Symbol (Symbol ~> Symbol) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Symbol]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Symbol] Symbol -> Type) t) Source #

SMonoid a => SMonoid (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Identity a) Source #

sMappend :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Identity a) (Identity a ~> Identity a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Identity a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Identity a] (Identity a) -> Type) t) Source #

SMonoid (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: First a) Source #

sMappend :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (First a) (First a ~> First a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [First a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [First a] (First a) -> Type) t) Source #

SMonoid (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Last a) Source #

sMappend :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Last a) (Last a ~> Last a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Last a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Last a] (Last a) -> Type) t) Source #

SMonoid a => SMonoid (Down a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Down a) Source #

sMappend :: forall (t1 :: Down a) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Down a) (Down a ~> Down a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Down a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Down a] (Down a) -> Type) t) Source #

(SOrd a, SBounded a) => SMonoid (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Max a) Source #

sMappend :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Max a) (Max a ~> Max a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Max a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Max a] (Max a) -> Type) t) Source #

(SOrd a, SBounded a) => SMonoid (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Min a) Source #

sMappend :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Min a) (Min a ~> Min a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Min a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Min a] (Min a) -> Type) t) Source #

SMonoid m => SMonoid (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

SMonoid a => SMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Dual a) Source #

sMappend :: forall (t1 :: Dual a) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Dual a) (Dual a ~> Dual a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Dual a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Dual a] (Dual a) -> Type) t) Source #

SNum a => SMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Product a) Source #

sMappend :: forall (t1 :: Product a) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Product a) (Product a ~> Product a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Product a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Product a] (Product a) -> Type) t) Source #

SNum a => SMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Sum a) Source #

sMappend :: forall (t1 :: Sum a) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Sum a) (Sum a ~> Sum a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Sum a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Sum a] (Sum a) -> Type) t) Source #

SSemigroup a => SMonoid (Maybe a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Maybe a) Source #

sMappend :: forall (t1 :: Maybe a) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Maybe a) (Maybe a ~> Maybe a) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Maybe a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Maybe a] (Maybe a) -> Type) t) Source #

SMonoid [a] Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: [a]) Source #

sMappend :: forall (t1 :: [a]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun [a] ([a] ~> [a]) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [[a]]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [[a]] [a] -> Type) t) Source #

SMonoid (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

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

sMappend :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Proxy s) (Proxy s ~> Proxy s) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Proxy s]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Proxy s] (Proxy s) -> Type) t) Source #

SMonoid b => SMonoid (a ~> b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: a ~> b) Source #

sMappend :: forall (t1 :: a ~> b) (t2 :: a ~> b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a ~> b) ((a ~> b) ~> (a ~> b)) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [a ~> b]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [a ~> b] (a ~> b) -> Type) t) Source #

(SMonoid a, SMonoid b) => SMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: (a, b)) Source #

sMappend :: forall (t1 :: (a, b)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a, b) ((a, b) ~> (a, b)) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [(a, b)]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [(a, b)] (a, b) -> Type) t) Source #

SMonoid a => SMonoid (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

sMempty :: Sing (MemptySym0 :: Const a b) Source #

sMappend :: forall (t1 :: Const a b) (t2 :: Const a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (Const a b) (Const a b ~> Const a b) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [Const a b]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Const a b] (Const a b) -> Type) t) Source #

(SMonoid a, SMonoid b, SMonoid c) => SMonoid (a, b, c) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing (MemptySym0 :: (a, b, c)) Source #

sMappend :: forall (t1 :: (a, b, c)) (t2 :: (a, b, c)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a, b, c) ((a, b, c) ~> (a, b, c)) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [(a, b, c)]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [(a, b, c)] (a, b, c) -> Type) 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 (MemptySym0 :: (a, b, c, d)) Source #

sMappend :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MappendSym0 :: TyFun (a, b, c, d) ((a, b, c, d) ~> (a, b, c, d)) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [(a, b, c, d)]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [(a, b, c, d)] (a, b, c, d) -> Type) 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 (MemptySym0 :: (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 (Apply (Apply (MappendSym0 :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> (a, b, c, d, e)) -> Type) t1) t2) Source #

sMconcat :: forall (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [(a, b, c, d, e)] (a, b, c, d, e) -> Type) 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) = Apply (Apply (TFHelper_6989586621679348493Sym0 :: TyFun a (f b ~> f a) -> Type) arg) arg1

Instances

Instances details
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 (a1 :: k1) <$ (a2 :: Identity b) 
Instance details

Defined in Data.Functor.Identity.Singletons

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: First b) 
Instance details

Defined in Data.Monoid.Singletons

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: Last b) 
Instance details

Defined in Data.Monoid.Singletons

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: Down b) 
Instance details

Defined in Data.Functor.Singletons

type (a1 :: k1) <$ (a2 :: Down b)
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 (a1 :: k1) <$ (a2 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: Min 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 (a1 :: k1) <$ (a2 :: Dual b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: Product b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: Sum b) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: k1) <$ (a2 :: Sum 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 (a1 :: k1) <$ (a2 :: NonEmpty b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a1 :: k1) <$ (a2 :: NonEmpty 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 (a1 :: k1) <$ (a2 :: Maybe b) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a1 :: k1) <$ (a2 :: 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 (a1 :: k1) <$ (a2 :: [b]) 
Instance details

Defined in Control.Monad.Singletons.Internal

type (a1 :: k1) <$ (a2 :: [b])
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 (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: f b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) t1) t2) infixl 4 Source #

default (%<$) :: forall a b (t1 :: a) (t2 :: f b). Apply (Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679348493Sym0 :: TyFun a (f b ~> f a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (f b ~> f a) -> Type) t1) t2) Source #

Instances

Instances details
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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Identity a ~> Identity b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Identity b ~> Identity a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (First a ~> First b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (First b ~> First a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Last a ~> Last b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Last b ~> Last a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Down a ~> Down b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Down b ~> Down a) -> Type) t1) t2) Source #

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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (First a ~> First b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (First b ~> First a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Last a ~> Last b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Last b ~> Last a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Max a ~> Max b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Max b ~> Max a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Min a ~> Min b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Min b ~> Min a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Dual a ~> Dual b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Dual b ~> Dual a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Product a ~> Product b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Product b ~> Product a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Sum a ~> Sum b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Sum b ~> Sum a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (NonEmpty a ~> NonEmpty b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (NonEmpty b ~> NonEmpty a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Maybe a ~> Maybe b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Maybe b ~> Maybe a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a ([b] ~> [a]) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Either a a ~> Either a b) -> Type) t1) t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: Either a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Either a b ~> Either a a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Proxy a ~> Proxy b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Proxy b ~> Proxy a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Arg a a ~> Arg a b) -> Type) t1) t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Arg a b ~> Arg a a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) ((a, a) ~> (a, b)) -> Type) t1) t2) Source #

(%<$) :: forall a0 b (t1 :: a0) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a ((a, b) ~> (a, a)) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Const m a ~> Const m b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Const m b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Const m b ~> Const m a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Product f g a ~> Product f g b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Product f g b ~> Product f g a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Sum f g a ~> Sum f g b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Sum f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Sum f g b ~> Sum f g a) -> Type) 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 (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Compose f g a ~> Compose f g b) -> Type) t1) t2) Source #

(%<$) :: forall a b (t1 :: a) (t2 :: Compose f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$@#@$) :: TyFun a (Compose f g b ~> Compose f g a) -> Type) t1) t2) Source #

type family (a1 :: a ~> b) <$> (a2 :: f a) :: f b where ... infixl 4 Source #

Equations

(a_6989586621679532912 :: a ~> b) <$> (a_6989586621679532914 :: f a) = Apply (Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) a_6989586621679532912) a_6989586621679532914 

(%<$>) :: forall a b (f :: Type -> Type) (t1 :: a ~> b) (t2 :: f a). SFunctor f => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<$>@#@$) :: TyFun (a ~> b) (f a ~> f b) -> Type) 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) = Apply (Apply (TFHelper_6989586621679348533Sym0 :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) 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) = Apply (Apply (Apply (LiftA2_6989586621679348549Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) arg) arg1) arg2

type (arg :: f a) *> (arg1 :: f b) :: f b infixl 4 Source #

type (arg :: f a) *> (arg1 :: f b) = Apply (Apply (TFHelper_6989586621679348565Sym0 :: TyFun (f a) (f b ~> f b) -> Type) arg) arg1

type (arg :: f a) <* (arg1 :: f b) :: f a infixl 4 Source #

type (arg :: f a) <* (arg1 :: f b) = Apply (Apply (TFHelper_6989586621679348576Sym0 :: TyFun (f a) (f b ~> f a) -> Type) arg) arg1

Instances

Instances details
PApplicative Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Data.Monoid.Singletons

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Data.Monoid.Singletons

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Control.Applicative.Singletons

type Pure (a :: k1)
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 First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a :: k1)
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 Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Pure (a :: k1)
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 NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Pure (a :: k1)
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 Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Control.Monad.Singletons.Internal

type Pure (a :: k1)
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 (a :: k1) 
Instance details

Defined in Data.Proxy.Singletons

type Pure (a :: k1)
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 (Apply (PureSym0 :: TyFun a (f a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: f (a ~> b)) (t2 :: f a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) t1) t2) infixl 4 Source #

default (%<*>) :: forall a b (t1 :: f (a ~> b)) (t2 :: f a). Apply (Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679348533Sym0 :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (f (a ~> b)) (f a ~> f b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) t1) t2) t3) Source #

default sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: f a) (t3 :: f b). Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) t1) t2) t3 ~ Apply (Apply (Apply (LiftA2_6989586621679348549Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) t1) t2) t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (f a ~> (f b ~> f c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: f a) (t2 :: f b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) t1) t2) infixl 4 Source #

default (%*>) :: forall a b (t1 :: f a) (t2 :: f b). Apply (Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679348565Sym0 :: TyFun (f a) (f b ~> f b) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (f a) (f b ~> f b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: f a) (t2 :: f b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) t1) t2) infixl 4 Source #

default (%<*) :: forall a b (t1 :: f a) (t2 :: f b). Apply (Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679348576Sym0 :: TyFun (f a) (f b ~> f a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (f a) (f b ~> f a) -> Type) t1) t2) Source #

Instances

Instances details
SApplicative Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Identity a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Identity (a ~> b)) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Identity (a ~> b)) (Identity a ~> Identity b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Identity a ~> (Identity b ~> Identity c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Identity a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Identity a) (Identity b ~> Identity b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Identity a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Identity a) (Identity b ~> Identity a) -> Type) t1) t2) Source #

SApplicative First Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (First a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: First (a ~> b)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (First (a ~> b)) (First a ~> First b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (First a ~> (First b ~> First c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (First a) (First b ~> First b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (First a) (First b ~> First a) -> Type) t1) t2) Source #

SApplicative Last Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Last a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Last (a ~> b)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Last (a ~> b)) (Last a ~> Last b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Last a ~> (Last b ~> Last c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Last a) (Last b ~> Last b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Last a) (Last b ~> Last a) -> Type) t1) t2) Source #

SApplicative Down Source # 
Instance details

Defined in Control.Applicative.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Down a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Down (a ~> b)) (t2 :: Down a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Down (a ~> b)) (Down a ~> Down b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Down a ~> (Down b ~> Down c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Down a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Down a) (Down b ~> Down b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Down a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Down a) (Down b ~> Down a) -> Type) t1) t2) Source #

SApplicative First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (First a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: First (a ~> b)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (First (a ~> b)) (First a ~> First b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (First a ~> (First b ~> First c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (First a) (First b ~> First b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (First a) (First b ~> First a) -> Type) t1) t2) Source #

SApplicative Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Last a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Last (a ~> b)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Last (a ~> b)) (Last a ~> Last b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Last a ~> (Last b ~> Last c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Last a) (Last b ~> Last b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Last a) (Last b ~> Last a) -> Type) t1) t2) Source #

SApplicative Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Max a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Max (a ~> b)) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Max (a ~> b)) (Max a ~> Max b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Max a ~> (Max b ~> Max c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Max a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Max a) (Max b ~> Max b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Max a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Max a) (Max b ~> Max a) -> Type) t1) t2) Source #

SApplicative Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Min a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Min (a ~> b)) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Min (a ~> b)) (Min a ~> Min b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Min a ~> (Min b ~> Min c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Min a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Min a) (Min b ~> Min b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Min a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Min a) (Min b ~> Min a) -> Type) t1) t2) Source #

SApplicative Dual Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Dual a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Dual (a ~> b)) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Dual (a ~> b)) (Dual a ~> Dual b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Dual a ~> (Dual b ~> Dual c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Dual a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Dual a) (Dual b ~> Dual b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Dual a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Dual a) (Dual b ~> Dual a) -> Type) t1) t2) Source #

SApplicative Product Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Product a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Product (a ~> b)) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Product (a ~> b)) (Product a ~> Product b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Product a ~> (Product b ~> Product c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Product a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Product a) (Product b ~> Product b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Product a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Product a) (Product b ~> Product a) -> Type) t1) t2) Source #

SApplicative Sum Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Sum a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Sum (a ~> b)) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Sum (a ~> b)) (Sum a ~> Sum b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Sum a ~> (Sum b ~> Sum c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Sum a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Sum a) (Sum b ~> Sum b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Sum a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Sum a) (Sum b ~> Sum a) -> Type) t1) t2) Source #

SApplicative NonEmpty Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (NonEmpty a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: NonEmpty (a ~> b)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (NonEmpty (a ~> b)) (NonEmpty a ~> NonEmpty b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (NonEmpty a ~> (NonEmpty b ~> NonEmpty c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty a) -> Type) t1) t2) Source #

SApplicative Maybe Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Maybe a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Maybe (a ~> b)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Maybe (a ~> b)) (Maybe a ~> Maybe b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Maybe a ~> (Maybe b ~> Maybe c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Maybe a) (Maybe b ~> Maybe a) -> Type) t1) t2) Source #

SApplicative [] Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a [a] -> Type) t) Source #

(%<*>) :: forall a b (t1 :: [a ~> b]) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun [a ~> b] ([a] ~> [b]) -> Type) t1) t2) Source #

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: [a]) (t3 :: [b]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun [a] ([b] ~> [b]) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun [a] ([b] ~> [a]) -> Type) t1) t2) Source #

SApplicative (Either e) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Either e a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Either e (a ~> b)) (t2 :: Either e a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Either e (a ~> b)) (Either e a ~> Either e b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Either e a ~> (Either e b ~> Either e c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Either e a) (t2 :: Either e b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Either e a) (Either e b ~> Either e b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Either e a) (t2 :: Either e b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Either e a) (Either e b ~> Either e a) -> Type) t1) t2) Source #

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

Defined in Data.Proxy.Singletons

Methods

sPure :: forall a (t :: a). Sing t -> Sing (Apply (PureSym0 :: TyFun a (Proxy a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Proxy (a ~> b)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Proxy (a ~> b)) (Proxy a ~> Proxy b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Proxy a ~> (Proxy b ~> Proxy c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy a) -> Type) t1) t2) Source #

SMonoid a => SApplicative ((,) a) Source # 
Instance details

Defined in Control.Applicative.Singletons

Methods

sPure :: forall a0 (t :: a0). Sing t -> Sing (Apply (PureSym0 :: TyFun a (a, a) -> Type) t) Source #

(%<*>) :: forall a0 b (t1 :: (a, a0 ~> b)) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (a, a ~> b) ((a, a) ~> (a, b)) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) ((a, a) ~> ((a, b) ~> (a, c))) -> Type) t1) t2) t3) Source #

(%*>) :: forall a0 b (t1 :: (a, a0)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (a, a) ((a, b) ~> (a, b)) -> Type) t1) t2) Source #

(%<*) :: forall a0 b (t1 :: (a, a0)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (a, a) ((a, b) ~> (a, a)) -> Type) 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 (Apply (PureSym0 :: TyFun a (Const m a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Const m (a ~> b)) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Const m (a ~> b)) (Const m a ~> Const m b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Const m a ~> (Const m b ~> Const m c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Const m a) (t2 :: Const m b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Const m a) (Const m b ~> Const m b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Const m a) (t2 :: Const m b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Const m a) (Const m b ~> Const m a) -> Type) 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 (Apply (PureSym0 :: TyFun a (Product f g a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Product f g (a ~> b)) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Product f g (a ~> b)) (Product f g a ~> Product f g b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Product f g a ~> (Product f g b ~> Product f g c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Product f g a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Product f g a) (Product f g b ~> Product f g b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Product f g a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Product f g a) (Product f g b ~> Product f g a) -> Type) 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 (Apply (PureSym0 :: TyFun a (Compose f g a) -> Type) t) Source #

(%<*>) :: forall a b (t1 :: Compose f g (a ~> b)) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*>@#@$) :: TyFun (Compose f g (a ~> b)) (Compose f g a ~> Compose f g b) -> Type) 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 (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Compose f g a ~> (Compose f g b ~> Compose f g c)) -> Type) t1) t2) t3) Source #

(%*>) :: forall a b (t1 :: Compose f g a) (t2 :: Compose f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((*>@#@$) :: TyFun (Compose f g a) (Compose f g b ~> Compose f g b) -> Type) t1) t2) Source #

(%<*) :: forall a b (t1 :: Compose f g a) (t2 :: Compose f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<*@#@$) :: TyFun (Compose f g a) (Compose f g b ~> Compose f g a) -> Type) 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) = Apply (Apply (TFHelper_6989586621679348604Sym0 :: TyFun (m a) (m b ~> m b) -> Type) arg) arg1

type Return (arg :: a) :: m a Source #

type Return (arg :: a) = Apply (Return_6989586621679348621Sym0 :: TyFun a (m a) -> Type) arg

Instances

Instances details
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 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 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 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 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 (Apply (Apply ((>>=@#@$) :: TyFun (m a) ((a ~> m b) ~> m b) -> Type) t1) t2) infixl 1 Source #

(%>>) :: forall a b (t1 :: m a) (t2 :: m b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) t1) t2) infixl 1 Source #

default (%>>) :: forall a b (t1 :: m a) (t2 :: m b). Apply (Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) t1) t2 ~ Apply (Apply (TFHelper_6989586621679348604Sym0 :: TyFun (m a) (m b ~> m b) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (m a) (m b ~> m b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (m a) -> Type) t) Source #

default sReturn :: forall a (t :: a). Apply (ReturnSym0 :: TyFun a (m a) -> Type) t ~ Apply (Return_6989586621679348621Sym0 :: TyFun a (m a) -> Type) t => Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (m a) -> Type) t) Source #

Instances

Instances details
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 (Apply (Apply ((>>=@#@$) :: TyFun (Identity a) ((a ~> Identity b) ~> Identity b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Identity a) (t2 :: Identity b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Identity a) (Identity b ~> Identity b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Identity a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (First a) ((a ~> First b) ~> First b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (First a) (First b ~> First b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (First a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Last a) ((a ~> Last b) ~> Last b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Last a) (Last b ~> Last b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Last a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Down a) ((a ~> Down b) ~> Down b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Down a) (t2 :: Down b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Down a) (Down b ~> Down b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Down a) -> Type) t) Source #

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 (Apply (Apply ((>>=@#@$) :: TyFun (First a) ((a ~> First b) ~> First b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: First a) (t2 :: First b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (First a) (First b ~> First b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (First a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Last a) ((a ~> Last b) ~> Last b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Last a) (t2 :: Last b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Last a) (Last b ~> Last b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Last a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Max a) ((a ~> Max b) ~> Max b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Max a) (t2 :: Max b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Max a) (Max b ~> Max b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Max a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Min a) ((a ~> Min b) ~> Min b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Min a) (t2 :: Min b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Min a) (Min b ~> Min b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Min a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Dual a) ((a ~> Dual b) ~> Dual b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Dual a) (t2 :: Dual b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Dual a) (Dual b ~> Dual b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Dual a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Product a) ((a ~> Product b) ~> Product b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Product a) (t2 :: Product b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Product a) (Product b ~> Product b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Product a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Sum a) ((a ~> Sum b) ~> Sum b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Sum a) (t2 :: Sum b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Sum a) (Sum b ~> Sum b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Sum a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (NonEmpty a) ((a ~> NonEmpty b) ~> NonEmpty b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: NonEmpty a) (t2 :: NonEmpty b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (NonEmpty a) (NonEmpty b ~> NonEmpty b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (NonEmpty a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Maybe a) ((a ~> Maybe b) ~> Maybe b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Maybe a) (t2 :: Maybe b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Maybe a) (Maybe b ~> Maybe b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Maybe a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun [a] ((a ~> [b]) ~> [b]) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: [a]) (t2 :: [b]). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun [a] ([b] ~> [b]) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a [a] -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Either e a) ((a ~> Either e b) ~> Either e b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Either e a) (t2 :: Either e b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Either e a) (Either e b ~> Either e b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Either e a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Proxy a) ((a ~> Proxy b) ~> Proxy b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Proxy a) (t2 :: Proxy b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Proxy a) (Proxy b ~> Proxy b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Proxy a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (a, a) ((a ~> (a, b)) ~> (a, b)) -> Type) t1) t2) Source #

(%>>) :: forall a0 b (t1 :: (a, a0)) (t2 :: (a, b)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (a, a) ((a, b) ~> (a, b)) -> Type) t1) t2) Source #

sReturn :: forall a0 (t :: a0). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (a, a) -> Type) t) 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 (Apply (Apply ((>>=@#@$) :: TyFun (Product f g a) ((a ~> Product f g b) ~> Product f g b) -> Type) t1) t2) Source #

(%>>) :: forall a b (t1 :: Product f g a) (t2 :: Product f g b). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((>>@#@$) :: TyFun (Product f g a) (Product f g b ~> Product f g b) -> Type) t1) t2) Source #

sReturn :: forall a (t :: a). Sing t -> Sing (Apply (ReturnSym0 :: TyFun a (Product f g a) -> Type) t) Source #

class PMonadFail (m :: k -> 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 (Apply (FailSym0 :: TyFun [Char] (m a) -> Type) t) Source #

Instances

Instances details
SMonadFail Maybe Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply (FailSym0 :: TyFun [Char] (Maybe a) -> Type) t) Source #

SMonadFail [] Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

Methods

sFail :: forall a (t :: [Char]). Sing t -> Sing (Apply (FailSym0 :: TyFun [Char] [a] -> Type) t) Source #

type family MapM_ (a1 :: a ~> m b) (a2 :: t a) :: m () where ... Source #

Equations

MapM_ (f :: a1 ~> m a2) (a_6989586621680390316 :: 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_6989586621680390316 

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 (Apply (Apply (MapM_Sym0 :: TyFun (a ~> m b) (t1 a ~> m ()) -> Type) t2) t3) Source #

type family Sequence_ (a1 :: t (m a)) :: m () where ... Source #

Equations

Sequence_ (a_6989586621680390293 :: 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_6989586621680390293 

sSequence_ :: forall (t1 :: Type -> Type) (m :: Type -> Type) a (t2 :: t1 (m a)). (SFoldable t1, SMonad m) => Sing t2 -> Sing (Apply (Sequence_Sym0 :: TyFun (t1 (m a)) (m ()) -> Type) 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 (Apply (Apply ((=<<@#@$) :: TyFun (a ~> m b) (m a ~> m b) -> Type) 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) = Apply (Apply (FoldMap_6989586621680390464Sym0 :: TyFun (a ~> m) (t a ~> m) -> Type) 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) = Apply (Apply (Apply (Foldr_6989586621680390478Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) 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) = Apply (Apply (Apply (Foldl_6989586621680390516Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) arg) arg1) arg2

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: t a) :: a Source #

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: t a) = Apply (Apply (Foldr1_6989586621680390553Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) arg) arg1

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: t a) :: a Source #

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: t a) = Apply (Apply (Foldl1_6989586621680390574Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) arg) arg1

type Elem (arg :: a) (arg1 :: t a) :: Bool Source #

type Elem (arg :: a) (arg1 :: t a) = Apply (Apply (Elem_6989586621680390639Sym0 :: TyFun a (t a ~> Bool) -> Type) arg) arg1

type Maximum (arg :: t a) :: a Source #

type Maximum (arg :: t a) = Apply (Maximum_6989586621680390653Sym0 :: TyFun (t a) a -> Type) arg

type Minimum (arg :: t a) :: a Source #

type Minimum (arg :: t a) = Apply (Minimum_6989586621680390668Sym0 :: TyFun (t a) a -> Type) arg

type Sum (arg :: t a) :: a Source #

type Sum (arg :: t a) = Apply (Sum_6989586621680390683Sym0 :: TyFun (t a) a -> Type) arg

type Product (arg :: t a) :: a Source #

type Product (arg :: t a) = Apply (Product_6989586621680390692Sym0 :: TyFun (t a) a -> Type) arg

Instances

Instances details
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 ~> k2) (a3 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Identity a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Identity a1)
type Foldr' (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldr' (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Identity a1)
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1)
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Identity a1)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Identity k2)
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 (a1 :: k1) (a2 :: Identity k1) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Elem (a1 :: k1) (a2 :: Identity k1)
type Maximum (a :: Identity k2) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Maximum (a :: Identity k2)
type Minimum (a :: Identity k2) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Minimum (a :: Identity k2)
type Sum (a :: Identity k2) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Sum (a :: Identity k2)
type Product (a :: Identity k2) 
Instance details

Defined in Data.Functor.Identity.Singletons

type Product (a :: Identity k2)
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 ~> k2) (a3 :: First a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: First a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 ~> k2) (a3 :: Last a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Last a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 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 ~> k2) (a3 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: First a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 ~> k2) (a3 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Last a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 ~> k2) (a3 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Max a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 ~> k2) (a3 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Min a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 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 ~> k2) (a3 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Dual a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Dual a1)
type Foldr' (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Dual a1)
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1)
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Dual a1)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Dual k2)
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 (a1 :: k1) (a2 :: Dual k1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a1 :: k1) (a2 :: Dual k1)
type Maximum (a :: Dual k2) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (a :: Dual k2)
type Minimum (a :: Dual k2) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (a :: Dual k2)
type Sum (a :: Dual k2) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a :: Dual k2)
type Product (a :: Dual k2) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a :: Dual k2)
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 ~> k2) (a3 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Product a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Product a1)
type Foldr' (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Product a1)
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1)
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Product a1)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Product k2)
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 (a1 :: k1) (a2 :: Product k1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a1 :: k1) (a2 :: Product k1)
type Maximum (a :: Product k2) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (a :: Product k2)
type Minimum (a :: Product k2) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (a :: Product k2)
type Sum (a :: Product k2) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a :: Product k2)
type Product (a :: Product k2) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a :: Product k2)
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 ~> k2) (a3 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Sum a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Sum a1)
type Foldr' (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr' (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Sum a1)
type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1)
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Sum a1)
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Sum k2)
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 (a1 :: k1) (a2 :: Sum k1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a1 :: k1) (a2 :: Sum k1)
type Maximum (a :: Sum k2) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (a :: Sum k2)
type Minimum (a :: Sum k2) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (a :: Sum k2)
type Sum (a :: Sum k2) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a :: Sum k2)
type Product (a :: Sum k2) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a :: Sum k2)
PFoldable NonEmpty Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold (a :: NonEmpty k2) 
Instance details

Defined in Data.Foldable.Singletons

type Fold (a :: NonEmpty k2)
type FoldMap (a2 :: a1 ~> k2) (a3 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: NonEmpty a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: NonEmpty a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2)
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: NonEmpty k2)
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 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 ~> k2) (a3 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type FoldMap (a2 :: a1 ~> k2) (a3 :: Maybe a1)
type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Maybe a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (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 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1])
type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl' (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: [a1])
type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldr1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2])
type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2]) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: [k2])
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 (a1 :: k1) (a2 :: [k1]) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a1 :: k1) (a2 :: [k1])
type Maximum (a :: [k2]) 
Instance details

Defined in Data.Foldable.Singletons

type Maximum (a :: [k2])
type Minimum (a :: [k2]) 
Instance details

Defined in Data.Foldable.Singletons

type Minimum (a :: [k2])
type Sum (a :: [k2]) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a :: [k2])
type Product (a :: [k2]) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a :: [k2])
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 k2) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (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 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (a4 :: Proxy a1) 
Instance details

Defined in Data.Foldable.Singletons

type Foldl (a2 :: k2 ~> (a1 ~> k2)) (a3 :: k2) (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 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2) 
Instance details

Defined in Data.Foldable.Singletons

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

Defined in Data.Foldable.Singletons

type Foldl1 (a1 :: k2 ~> (k2 ~> k2)) (a2 :: Proxy k2)
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 (a1 :: k1) (a2 :: Proxy k1) 
Instance details

Defined in Data.Foldable.Singletons

type Elem (a1 :: k1) (a2 :: Proxy k1)
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 (a :: Proxy k2) 
Instance details

Defined in Data.Foldable.Singletons

type Sum (a :: Proxy k2)
type Product (a :: Proxy k2) 
Instance details

Defined in Data.Foldable.Singletons

type Product (a :: Proxy k2)
PFoldable (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

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 (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) t1) t2) Source #

default sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: t a). (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) t1) t2 ~ Apply (Apply (FoldMap_6989586621680390464Sym0 :: TyFun (a ~> m) (t a ~> m) -> Type) t1) t2, SMonoid m) => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: t a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3) Source #

default sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: t a). Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3 ~ Apply (Apply (Apply (Foldr_6989586621680390478Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: t a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3) Source #

default sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: t a). Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3 ~ Apply (Apply (Apply (Foldl_6989586621680390516Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2) Source #

default sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2 ~ Apply (Apply (Foldr1_6989586621680390553Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2) Source #

default sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: t a). Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2 ~ Apply (Apply (Foldl1_6989586621680390574Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) t1) t2) Source #

sElem :: forall a (t1 :: a) (t2 :: t a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) t1) t2) Source #

default sElem :: forall a (t1 :: a) (t2 :: t a). (Apply (Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) t1) t2 ~ Apply (Apply (Elem_6989586621680390639Sym0 :: TyFun a (t a ~> Bool) -> Type) t1) t2, SEq a) => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: t a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (t a) a -> Type) t1) Source #

default sMaximum :: forall a (t1 :: t a). (Apply (MaximumSym0 :: TyFun (t a) a -> Type) t1 ~ Apply (Maximum_6989586621680390653Sym0 :: TyFun (t a) a -> Type) t1, SOrd a) => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (t a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: t a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (t a) a -> Type) t1) Source #

default sMinimum :: forall a (t1 :: t a). (Apply (MinimumSym0 :: TyFun (t a) a -> Type) t1 ~ Apply (Minimum_6989586621680390668Sym0 :: TyFun (t a) a -> Type) t1, SOrd a) => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (t a) a -> Type) t1) Source #

sSum :: forall a (t1 :: t a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (t a) a -> Type) t1) Source #

default sSum :: forall a (t1 :: t a). (Apply (SumSym0 :: TyFun (t a) a -> Type) t1 ~ Apply (Sum_6989586621680390683Sym0 :: TyFun (t a) a -> Type) t1, SNum a) => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (t a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: t a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (t a) a -> Type) t1) Source #

default sProduct :: forall a (t1 :: t a). (Apply (ProductSym0 :: TyFun (t a) a -> Type) t1 ~ Apply (Product_6989586621680390692Sym0 :: TyFun (t a) a -> Type) t1, SNum a) => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (t a) a -> Type) t1) Source #

Instances

Instances details
SFoldable Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

sFold :: forall m (t1 :: Identity m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Identity m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Identity a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Identity a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Identity a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Identity a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Identity a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Identity a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Identity a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Identity a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Identity a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Identity a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Identity a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Identity a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Identity a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Identity a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Identity a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Identity a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Identity a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Identity a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Identity a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Identity a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Identity a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Identity a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Identity a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Identity a) a -> Type) t1) Source #

SFoldable First Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: First m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (First m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: First a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (First a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (First a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (First a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (First a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (First a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (First a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (First a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: First a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (First a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: First a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (First a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: First a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (First a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: First a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (First a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: First a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (First a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: First a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (First a) a -> Type) t1) Source #

sSum :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (First a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (First a) a -> Type) t1) Source #

SFoldable Last Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Last m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Last m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Last a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Last a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Last a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Last a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Last a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Last a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Last a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Last a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Last a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Last a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Last a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Last a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Last a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Last a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Last a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Last a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Last a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Last a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Last a) a -> Type) t1) Source #

SFoldable First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: First m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (First m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: First a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (First a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (First a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (First a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (First a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (First a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (First a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (First a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: First a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (First a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: First a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (First a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: First a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (First a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: First a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (First a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: First a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (First a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: First a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (First a) a -> Type) t1) Source #

sSum :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (First a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (First a) a -> Type) t1) Source #

SFoldable Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: Last m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Last m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Last a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Last a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Last a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Last a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Last a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Last a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Last a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Last a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Last a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Last a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Last a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Last a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Last a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Last a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Last a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Last a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Last a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Last a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Last a) a -> Type) t1) Source #

SFoldable Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: Max m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Max m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Max a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Max a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Max a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Max a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Max a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Max a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Max a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Max a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Max a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Max a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Max a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Max a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Max a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Max a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Max a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Max a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Max a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Max a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Max a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Max a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Max a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Max a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Max a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Max a) a -> Type) t1) Source #

SFoldable Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sFold :: forall m (t1 :: Min m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Min m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Min a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Min a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Min a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Min a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Min a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Min a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Min a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Min a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Min a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Min a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Min a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Min a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Min a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Min a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Min a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Min a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Min a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Min a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Min a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Min a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Min a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Min a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Min a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Min a) a -> Type) t1) Source #

SFoldable Dual Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Dual m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Dual m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Dual a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Dual a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Dual a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Dual a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Dual a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Dual a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Dual a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Dual a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Dual a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Dual a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Dual a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Dual a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Dual a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Dual a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Dual a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Dual a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Dual a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Dual a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Dual a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Dual a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Dual a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Dual a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Dual a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Dual a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Dual a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Dual a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Dual a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Dual a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Dual a) a -> Type) t1) Source #

SFoldable Product Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Product m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Product m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Product a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Product a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Product a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Product a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Product a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Product a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Product a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Product a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Product a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Product a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Product a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Product a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Product a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Product a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Product a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Product a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Product a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Product a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Product a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Product a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Product a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Product a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Product a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Product a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Product a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Product a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Product a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Product a) a -> Type) t1) Source #

SFoldable Sum Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Sum m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Sum m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Sum a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Sum a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Sum a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Sum a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Sum a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Sum a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Sum a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Sum a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Sum a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Sum a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Sum a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Sum a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Sum a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Sum a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Sum a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Sum a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Sum a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Sum a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Sum a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Sum a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Sum a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Sum a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Sum a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Sum a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Sum a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Sum a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Sum a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Sum a) a -> Type) t1) Source #

SFoldable NonEmpty Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: NonEmpty m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (NonEmpty m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: NonEmpty a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (NonEmpty a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (NonEmpty a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (NonEmpty a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (NonEmpty a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (NonEmpty a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: NonEmpty a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (NonEmpty a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (NonEmpty a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (NonEmpty a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (NonEmpty a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: NonEmpty a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (NonEmpty a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: NonEmpty a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (NonEmpty a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: NonEmpty a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (NonEmpty a) a -> Type) t1) Source #

sSum :: forall a (t1 :: NonEmpty a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (NonEmpty a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: NonEmpty a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (NonEmpty a) a -> Type) t1) Source #

SFoldable Maybe Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: Maybe m). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (Maybe m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Maybe a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Maybe a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Maybe a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Maybe a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Maybe a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Maybe a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Maybe a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Maybe a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Maybe a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Maybe a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Maybe a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Maybe a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Maybe a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Maybe a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Maybe a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Maybe a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Maybe a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Maybe a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Maybe a) a -> Type) t1) Source #

SFoldable [] Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: [m]). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun [m] m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: [a]). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) ([a] ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: [a]). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun [a] [a] -> Type) t1) Source #

sNull :: forall a (t1 :: [a]). Sing t1 -> Sing (Apply (NullSym0 :: TyFun [a] Bool -> Type) t1) Source #

sLength :: forall a (t1 :: [a]). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun [a] Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a ([a] ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: [a]). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun [a] a -> Type) t1) Source #

sMinimum :: forall a (t1 :: [a]). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun [a] a -> Type) t1) Source #

sSum :: forall a (t1 :: [a]). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun [a] a -> Type) t1) Source #

sProduct :: forall a (t1 :: [a]). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun [a] a -> Type) 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 (Apply (FoldSym0 :: TyFun (Either a m) m -> Type) t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: Either a a0). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Either a a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: Either a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Either a a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Either a a ~> b)) -> Type) 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 (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Either a a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Either a a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Either a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Either a a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Either a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Either a a ~> a) -> Type) t1) t2) Source #

sToList :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Either a a) [a] -> Type) t1) Source #

sNull :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Either a a) Bool -> Type) t1) Source #

sLength :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Either a a) Natural -> Type) t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: Either a a0). SEq a0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Either a a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a0 (t1 :: Either a a0). SOrd a0 => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Either a a) a -> Type) t1) Source #

sMinimum :: forall a0 (t1 :: Either a a0). SOrd a0 => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Either a a) a -> Type) t1) Source #

sSum :: forall a0 (t1 :: Either a a0). SNum a0 => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Either a a) a -> Type) t1) Source #

sProduct :: forall a0 (t1 :: Either a a0). SNum a0 => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Either a a) a -> Type) 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 (Apply (FoldSym0 :: TyFun (Proxy m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Proxy a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Proxy a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Proxy a ~> b)) -> Type) t1) t2) t3) Source #

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

sFoldl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: Proxy a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Proxy a ~> b)) -> Type) t1) t2) t3) Source #

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

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Proxy a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Proxy a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Proxy a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Proxy a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Proxy a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Proxy a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Proxy a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Proxy a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Proxy a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Proxy a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Proxy a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Proxy a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Proxy a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Proxy a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Proxy a) a -> Type) 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 (Apply (FoldSym0 :: TyFun (Arg a m) m -> Type) t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: Arg a a0). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Arg a a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: Arg a a0). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Arg a a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Arg a a ~> b)) -> Type) 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 (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Arg a a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Arg a a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Arg a a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Arg a a ~> a) -> Type) t1) t2) Source #

sToList :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Arg a a) [a] -> Type) t1) Source #

sNull :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Arg a a) Bool -> Type) t1) Source #

sLength :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Arg a a) Natural -> Type) t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: Arg a a0). SEq a0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Arg a a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a0 (t1 :: Arg a a0). SOrd a0 => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Arg a a) a -> Type) t1) Source #

sMinimum :: forall a0 (t1 :: Arg a a0). SOrd a0 => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Arg a a) a -> Type) t1) Source #

sSum :: forall a0 (t1 :: Arg a a0). SNum a0 => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Arg a a) a -> Type) t1) Source #

sProduct :: forall a0 (t1 :: Arg a a0). SNum a0 => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Arg a a) a -> Type) t1) Source #

SFoldable ((,) a) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: (a, m)). SMonoid m => Sing t1 -> Sing (Apply (FoldSym0 :: TyFun (a, m) m -> Type) t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: (a, a0)). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) ((a, a) ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: (a, a0)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ((a, a) ~> b)) -> Type) t1) t2) t3) Source #

sFoldr' :: forall a0 b (t1 :: a0 ~> (b ~> b)) (t2 :: b) (t3 :: (a, a0)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> ((a, a) ~> b)) -> Type) t1) t2) t3) Source #

sFoldl :: forall b a0 (t1 :: b ~> (a0 ~> b)) (t2 :: b) (t3 :: (a, a0)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ((a, a) ~> b)) -> Type) t1) t2) t3) Source #

sFoldl' :: forall b a0 (t1 :: b ~> (a0 ~> b)) (t2 :: b) (t3 :: (a, a0)). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> ((a, a) ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) ((a, a) ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) ((a, a) ~> a) -> Type) t1) t2) Source #

sToList :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (a, a) [a] -> Type) t1) Source #

sNull :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (a, a) Bool -> Type) t1) Source #

sLength :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (a, a) Natural -> Type) t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: (a, a0)). SEq a0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a ((a, a) ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a0 (t1 :: (a, a0)). SOrd a0 => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (a, a) a -> Type) t1) Source #

sMinimum :: forall a0 (t1 :: (a, a0)). SOrd a0 => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (a, a) a -> Type) t1) Source #

sSum :: forall a0 (t1 :: (a, a0)). SNum a0 => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (a, a) a -> Type) t1) Source #

sProduct :: forall a0 (t1 :: (a, a0)). SNum a0 => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (a, a) a -> Type) 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 (Apply (FoldSym0 :: TyFun (Const m m) m -> Type) t1) Source #

sFoldMap :: forall a m0 (t1 :: a ~> m0) (t2 :: Const m a). SMonoid m0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Const m a ~> m) -> Type) t1) t2) Source #

sFoldr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: Const m a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Const m a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Const m a ~> b)) -> Type) 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 (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Const m a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Const m a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Const m a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Const m a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Const m a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Const m a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Const m a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Const m a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Const m a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Const m a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Const m a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Const m a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Const m a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Const m a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Const m a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Const m a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Const m a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Const m a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Const m a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Const m a) a -> Type) 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 (Apply (FoldSym0 :: TyFun (Product f g m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Product f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Product f g a ~> m) -> Type) 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 (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Product f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Product f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Product f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Product f g a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Product f g a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Product f g a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Product f g a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Product f g a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Product f g a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Product f g a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Product f g a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Product f g a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Product f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Product f g a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Product f g a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Product f g a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Product f g a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Product f g a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Product f g a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Product f g a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Product f g a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Product f g a) a -> Type) 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 (Apply (FoldSym0 :: TyFun (Sum f g m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Sum f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Sum f g a ~> m) -> Type) 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 (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Sum f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Sum f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Sum f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Sum f g a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Sum f g a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Sum f g a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Sum f g a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Sum f g a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Sum f g a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Sum f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Sum f g a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Sum f g a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Sum f g a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Sum f g a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Sum f g a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Sum f g a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Sum f g a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Sum f g a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Sum f g a) a -> Type) 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 (Apply (FoldSym0 :: TyFun (Compose f g m) m -> Type) t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Compose f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (FoldMapSym0 :: TyFun (a ~> m) (Compose f g a ~> m) -> Type) 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 (Apply (Apply (Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (Compose f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (Compose f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (Compose f g a ~> b)) -> Type) 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 (Apply (Apply (Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (Compose f g a ~> b)) -> Type) t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (Compose f g a ~> a) -> Type) t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (Compose f g a ~> a) -> Type) t1) t2) Source #

sToList :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (Apply (ToListSym0 :: TyFun (Compose f g a) [a] -> Type) t1) Source #

sNull :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (Apply (NullSym0 :: TyFun (Compose f g a) Bool -> Type) t1) Source #

sLength :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (Apply (LengthSym0 :: TyFun (Compose f g a) Natural -> Type) t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Compose f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ElemSym0 :: TyFun a (Compose f g a ~> Bool) -> Type) t1) t2) Source #

sMaximum :: forall a (t1 :: Compose f g a). SOrd a => Sing t1 -> Sing (Apply (MaximumSym0 :: TyFun (Compose f g a) a -> Type) t1) Source #

sMinimum :: forall a (t1 :: Compose f g a). SOrd a => Sing t1 -> Sing (Apply (MinimumSym0 :: TyFun (Compose f g a) a -> Type) t1) Source #

sSum :: forall a (t1 :: Compose f g a). SNum a => Sing t1 -> Sing (Apply (SumSym0 :: TyFun (Compose f g a) a -> Type) t1) Source #

sProduct :: forall a (t1 :: Compose f g a). SNum a => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Compose f g a) a -> Type) 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) = Apply (Apply (Traverse_6989586621680734001Sym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) arg) arg1

type SequenceA (arg :: t (f a)) :: f (t a) Source #

type SequenceA (arg :: t (f a)) = Apply (SequenceA_6989586621680734013Sym0 :: TyFun (t (f a)) (f (t a)) -> Type) arg

type MapM (arg :: a ~> m b) (arg1 :: t a) :: m (t b) Source #

type MapM (arg :: a ~> m b) (arg1 :: t a) = Apply (Apply (MapM_6989586621680734023Sym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) arg) arg1

type Sequence (arg :: t (m a)) :: m (t a) Source #

type Sequence (arg :: t (m a)) = Apply (Sequence_6989586621680734037Sym0 :: TyFun (t (m a)) (m (t a)) -> Type) arg

Instances

Instances details
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 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 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 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 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 (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 (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) t1) t2) Source #

default sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: t a). (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) t1) t2 ~ Apply (Apply (Traverse_6989586621680734001Sym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) t1) t2, SApplicative f) => Sing t1 -> Sing t2 -> Sing (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: t (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) t1) Source #

default sSequenceA :: forall (f :: Type -> Type) a (t1 :: t (f a)). (Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) t1 ~ Apply (SequenceA_6989586621680734013Sym0 :: TyFun (t (f a)) (f (t a)) -> Type) t1, SApplicative f) => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: t a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) t1) t2) Source #

default sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: t a). (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) t1) t2 ~ Apply (Apply (MapM_6989586621680734023Sym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) t1) t2, SMonad m) => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: t (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) t1) Source #

default sSequence :: forall (m :: Type -> Type) a (t1 :: t (m a)). (Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) t1 ~ Apply (Sequence_6989586621680734037Sym0 :: TyFun (t (m a)) (m (t a)) -> Type) t1, SMonad m) => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) t1) Source #

Instances

Instances details
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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Identity a ~> f (Identity b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Identity (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Identity (f a)) (f (Identity a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Identity a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Identity a ~> m (Identity b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Identity (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Identity (m a)) (m (Identity a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (First a ~> f (First b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: First (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (First (f a)) (f (First a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: First a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (First a ~> m (First b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: First (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (First (m a)) (m (First a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Last a ~> f (Last b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Last (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Last (f a)) (f (Last a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Last a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Last a ~> m (Last b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Last (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Last (m a)) (m (Last a)) -> Type) t1) Source #

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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (First a ~> f (First b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: First (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (First (f a)) (f (First a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: First a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (First a ~> m (First b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: First (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (First (m a)) (m (First a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Last a ~> f (Last b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Last (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Last (f a)) (f (Last a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Last a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Last a ~> m (Last b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Last (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Last (m a)) (m (Last a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Max a ~> f (Max b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Max (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Max (f a)) (f (Max a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Max a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Max a ~> m (Max b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Max (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Max (m a)) (m (Max a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Min a ~> f (Min b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Min (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Min (f a)) (f (Min a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Min a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Min a ~> m (Min b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Min (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Min (m a)) (m (Min a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Dual a ~> f (Dual b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Dual (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Dual (f a)) (f (Dual a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Dual a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Dual a ~> m (Dual b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Dual (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Dual (m a)) (m (Dual a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Product a ~> f (Product b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Product (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Product (f a)) (f (Product a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Product a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Product a ~> m (Product b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Product (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Product (m a)) (m (Product a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Sum a ~> f (Sum b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Sum (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Sum (f a)) (f (Sum a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Sum a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Sum a ~> m (Sum b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Sum (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Sum (m a)) (m (Sum a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (NonEmpty a ~> f (NonEmpty b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: NonEmpty (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (NonEmpty (f a)) (f (NonEmpty a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: NonEmpty a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (NonEmpty a ~> m (NonEmpty b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: NonEmpty (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (NonEmpty (m a)) (m (NonEmpty a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Maybe a ~> f (Maybe b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Maybe (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Maybe (f a)) (f (Maybe a)) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: Maybe a). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Maybe a ~> m (Maybe b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Maybe (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Maybe (m a)) (m (Maybe a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) ([a] ~> f [b]) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: [f a]). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun [f a] (f [a]) -> Type) t1) Source #

sMapM :: forall a (m :: Type -> Type) b (t1 :: a ~> m b) (t2 :: [a]). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) ([a] ~> m [b]) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: [m a]). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun [m a] (m [a]) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Either a a ~> f (Either a b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: Either a (f a0)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Either a (f a)) (f (Either a a)) -> Type) t1) Source #

sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: Either a a0). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Either a a ~> m (Either a b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a0 (t1 :: Either a (m a0)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Either a (m a)) (m (Either a a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Proxy a ~> f (Proxy b)) -> Type) t1) t2) Source #

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

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

sSequence :: forall (m :: Type -> Type) a (t1 :: Proxy (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Proxy (m a)) (m (Proxy a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Arg a a ~> f (Arg a b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: Arg a (f a0)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Arg a (f a)) (f (Arg a a)) -> Type) t1) Source #

sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: Arg a a0). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Arg a a ~> m (Arg a b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a0 (t1 :: Arg a (m a0)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Arg a (m a)) (m (Arg a a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) ((a, a) ~> f (a, b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: (a, f a0)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (a, f a) (f (a, a)) -> Type) t1) Source #

sMapM :: forall a0 (m :: Type -> Type) b (t1 :: a0 ~> m b) (t2 :: (a, a0)). SMonad m => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) ((a, a) ~> m (a, b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a0 (t1 :: (a, m a0)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (a, m a) (m (a, a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Const m a ~> f (Const m b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Const m (f a)). SApplicative f => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Const m (f a)) (f (Const m a)) -> Type) t1) Source #

sMapM :: forall a (m0 :: Type -> Type) b (t1 :: a ~> m0 b) (t2 :: Const m a). SMonad m0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Const m a ~> m (Const m b)) -> Type) t1) t2) Source #

sSequence :: forall (m0 :: Type -> Type) a (t1 :: Const m (m0 a)). SMonad m0 => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Const m (m a)) (m (Const m a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Product f g a ~> f (Product f g b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Product f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Product f g (f a)) (f (Product f g a)) -> Type) 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 (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Product f g a ~> m (Product f g b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Product f g (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Product f g (m a)) (m (Product f g a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Sum f g a ~> f (Sum f g b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Sum f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Sum f g (f a)) (f (Sum f g a)) -> Type) 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 (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Sum f g a ~> m (Sum f g b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Sum f g (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Sum f g (m a)) (m (Sum f g a)) -> Type) 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 (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Compose f g a ~> f (Compose f g b)) -> Type) t1) t2) Source #

sSequenceA :: forall (f0 :: Type -> Type) a (t1 :: Compose f g (f0 a)). SApplicative f0 => Sing t1 -> Sing (Apply (SequenceASym0 :: TyFun (Compose f g (f a)) (f (Compose f g a)) -> Type) 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 (Apply (Apply (MapMSym0 :: TyFun (a ~> m b) (Compose f g a ~> m (Compose f g b)) -> Type) t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Compose f g (m a)). SMonad m => Sing t1 -> Sing (Apply (SequenceSym0 :: TyFun (Compose f g (m a)) (m (Compose f g a)) -> Type) 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 (Apply (IdSym0 :: TyFun a a -> Type) 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 (Apply (Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) t1) t2) Source #

type family ((a1 :: b ~> c) . (a2 :: a ~> b)) (a3 :: a) :: c where ... infixr 9 Source #

Equations

((f :: k2 ~> k3) . (g :: k4 ~> k2)) (a_6989586621679180201 :: k4) = Apply (Apply (Apply (Apply (Lambda_6989586621679180213Sym0 :: TyFun (k2 ~> k3) (TyFun (k4 ~> k2) (TyFun k4 (TyFun k4 k3 -> Type) -> Type) -> Type) -> Type) f) g) a_6989586621679180201) a_6989586621679180201 

(%.) :: forall b c a (t1 :: b ~> c) (t2 :: a ~> b) (t3 :: a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ((.@#@$) :: TyFun (b ~> c) ((a ~> b) ~> (a ~> c)) -> Type) 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 (Apply (Apply (Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) 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 (Apply (Apply (($@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) 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_6989586621679180143 :: k2) = Apply (Let6989586621679180155GoSym3 p f a_6989586621679180143) a_6989586621679180143 

sUntil :: forall a (t1 :: a ~> Bool) (t2 :: a ~> a) (t3 :: a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) t1) t2) t3) Source #

type family AsTypeOf (a1 :: a) (a2 :: a) :: a where ... Source #

Equations

AsTypeOf (a_6989586621679180180 :: k1) (a_6989586621679180182 :: k1) = Apply (Apply (ConstSym0 :: TyFun k1 (k1 ~> k1) -> Type) a_6989586621679180180) a_6989586621679180182 

sAsTypeOf :: forall a (t1 :: a) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) 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 (str :: Symbol) a. HasCallStack => Sing str -> a Source #

The singleton for error.

type family ErrorWithoutStackTrace (str :: Symbol) :: a where ... Source #

The promotion of errorWithoutStackTrace.

sErrorWithoutStackTrace :: forall (str :: Symbol) a. Sing str -> a Source #

The singleton for errorWithoutStackTrace.

type family Undefined :: a where ... Source #

The promotion of undefined.

sUndefined :: HasCallStack => a Source #

The singleton for 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 (Apply (Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) t1) t2) infixr 0 Source #

type family (a1 :: a ~> b) $! (a2 :: a) :: b where ... infixr 0 Source #

Equations

(f :: k ~> k2) $! (x :: k) = Apply f (Let6989586621679180171VxSym2 f x) 

(%$!) :: forall a b (t1 :: a ~> b) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (($!@#@$) :: TyFun (a ~> b) (a ~> b) -> Type) 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 (Apply (Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) 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 (Apply (Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) 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]) = Case_6989586621679815061 p x xs (Let6989586621679815059Scrutinee_6989586621679811550Sym3 p x xs) 

sFilter :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 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 (Apply (HeadSym0 :: TyFun [a] a -> Type) 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 (Apply (LastSym0 :: TyFun [a] a -> Type) 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 (Apply (TailSym0 :: TyFun [a] [a] -> Type) 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 (Let6989586621679815804Init'Sym2 x xs :: TyFun k1 ([k1] ~> [k1]) -> Type) x) xs 

sInit :: forall a (t :: [a]). Sing t -> Sing (Apply (InitSym0 :: TyFun [a] [a] -> Type) 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 :: [k]) !! n = Case_6989586621679814668 x xs n (Let6989586621679814666Scrutinee_6989586621679811590Sym3 x xs n) 

(%!!) :: forall a (t1 :: [a]) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) t1) t2) infixl 9 Source #

type family Null (arg :: t a) :: Bool Source #

Instances

Instances details
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 (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 (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 :: NonEmpty a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Null (arg :: NonEmpty a)
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 (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 :: Arg a1 a2) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Arg a1 a2)
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 (Apply (NullSym0 :: TyFun (t a) Bool -> Type) t1) Source #

type family Length (arg :: t a) :: Natural Source #

Instances

Instances details
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 (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 (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 :: NonEmpty a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Length (arg :: NonEmpty a)
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 (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 :: Arg a1 a2) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Arg a1 a2)
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 (Apply (LengthSym0 :: TyFun (t a) Natural -> Type) t1) Source #

type family Reverse (a1 :: [a]) :: [a] where ... Source #

Equations

Reverse (l :: [a6989586621679811119]) = Apply (Apply (Let6989586621679815788RevSym1 l :: TyFun [a6989586621679811119] ([a6989586621679811119] ~> [a6989586621679811119]) -> Type) l) (NilSym0 :: [a6989586621679811119]) 

sReverse :: forall a (t :: [a]). Sing t -> Sing (Apply (ReverseSym0 :: TyFun [a] [a] -> Type) t) Source #

Special folds

type family And (a :: t Bool) :: Bool where ... Source #

Equations

And (a_6989586621680390254 :: 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_6989586621680390254 

sAnd :: forall (t1 :: Type -> Type) (t2 :: t1 Bool). SFoldable t1 => Sing t2 -> Sing (Apply (AndSym0 :: TyFun (t1 Bool) Bool -> Type) t2) Source #

type family Or (a :: t Bool) :: Bool where ... Source #

Equations

Or (a_6989586621680390248 :: 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_6989586621680390248 

sOr :: forall (t1 :: Type -> Type) (t2 :: t1 Bool). SFoldable t1 => Sing t2 -> Sing (Apply (OrSym0 :: TyFun (t1 Bool) Bool -> Type) t2) Source #

type family Any (a1 :: a ~> Bool) (a2 :: t a) :: Bool where ... Source #

Equations

Any (p :: a ~> Bool) (a_6989586621680390239 :: 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_6989586621680390239 

sAny :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (AnySym0 :: TyFun (a ~> Bool) (t1 a ~> Bool) -> Type) t2) t3) Source #

type family All (a1 :: a ~> Bool) (a2 :: t a) :: Bool where ... Source #

Equations

All (p :: a ~> Bool) (a_6989586621680390230 :: 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_6989586621680390230 

sAll :: forall a (t1 :: Type -> Type) (t2 :: a ~> Bool) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (AllSym0 :: TyFun (a ~> Bool) (t1 a ~> Bool) -> Type) 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) (Apply (Lambda_6989586621680390276Sym0 :: TyFun (t [a]) (TyFun [a] (TyFun [a] [a] -> Type) -> Type) -> Type) xs)) (NilSym0 :: [a])) xs 

sConcat :: forall (t1 :: Type -> Type) a (t2 :: t1 [a]). SFoldable t1 => Sing t2 -> Sing (Apply (ConcatSym0 :: TyFun (t1 [a]) [a] -> Type) t2) Source #

type family ConcatMap (a1 :: a ~> [b]) (a2 :: t a) :: [b] where ... Source #

Equations

ConcatMap (f :: a1 ~> [a2]) (xs :: t a1) = Apply (Apply (Apply (FoldrSym0 :: TyFun (a1 ~> ([a2] ~> [a2])) ([a2] ~> (t a1 ~> [a2])) -> Type) (Apply (Apply (Lambda_6989586621680390267Sym0 :: TyFun (a1 ~> [a2]) (TyFun (t a1) (TyFun a1 (TyFun [a2] [a2] -> Type) -> Type) -> Type) -> Type) f) xs)) (NilSym0 :: [a2])) xs 

sConcatMap :: forall a b (t1 :: Type -> Type) (t2 :: a ~> [b]) (t3 :: t1 a). SFoldable t1 => Sing t2 -> Sing t3 -> Sing (Apply (Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t1 a ~> [b]) -> Type) t2) t3) Source #

Building lists

Scans

type family Scanl (a1 :: b ~> (a ~> b)) (a2 :: b) (a3 :: [a]) :: [b] where ... Source #

Equations

Scanl (f :: a ~> (k1 ~> a)) (q :: a) (ls :: [k1]) = Apply (Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) q) (Case_6989586621679815597 f q ls ls) 

sScanl :: forall b a (t1 :: b ~> (a ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) 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 (Apply (Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) 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 :: k ~> (k1 ~> k1)) (q0 :: k1) (x ': xs :: [k]) = Case_6989586621679815574 f q0 x xs (Let6989586621679815572Scrutinee_6989586621679811480Sym4 f q0 x xs) 

sScanr :: forall a b (t1 :: a ~> (b ~> b)) (t2 :: b) (t3 :: [a]). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) 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 :: k ~> (k ~> k)) (x ': (wild_6989586621679811492 ': wild_6989586621679811494) :: [k]) = Case_6989586621679815555 f x wild_6989586621679811492 wild_6989586621679811494 (Let6989586621679815553Scrutinee_6989586621679811486Sym4 f x wild_6989586621679811492 wild_6989586621679811494) 

sScanr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) t1) t2) Source #

Infinite lists

type family Replicate (a1 :: Natural) (a2 :: a) :: [a] where ... Source #

Equations

Replicate n (x :: k) = Case_6989586621679814687 n x (Let6989586621679814685Scrutinee_6989586621679811588Sym2 n x) 

sReplicate :: forall a (t1 :: Natural) (t2 :: a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) t1) t2) Source #

Sublists

type family Take (a1 :: Natural) (a2 :: [a]) :: [a] where ... Source #

Equations

Take _1 ('[] :: [a]) = NilSym0 :: [a] 
Take n (x ': xs :: [k]) = Case_6989586621679814843 n x xs (Let6989586621679814841Scrutinee_6989586621679811572Sym3 n x xs) 

sTake :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) t1) t2) Source #

type family Drop (a1 :: Natural) (a2 :: [a]) :: [a] where ... Source #

Equations

Drop _1 ('[] :: [a]) = NilSym0 :: [a] 
Drop n (x ': xs :: [k]) = Case_6989586621679814830 n x xs (Let6989586621679814828Scrutinee_6989586621679811574Sym3 n x xs) 

sDrop :: forall a (t1 :: Natural) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) 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]) = Case_6989586621679814960 p x xs (Let6989586621679814958Scrutinee_6989586621679811562Sym3 p x xs) 

sTakeWhile :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 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]) = Case_6989586621679814947 p x xs' (Let6989586621679814945Scrutinee_6989586621679811564Sym3 p x xs') 

sDropWhile :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) 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) (Let6989586621679814886XsSym0 :: [a])) (Let6989586621679814886XsSym0 :: [a]) 
Span (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Case_6989586621679814895 p x xs' (Let6989586621679814893Scrutinee_6989586621679811568Sym3 p x xs') 

sSpan :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 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) (Let6989586621679814851XsSym0 :: [a])) (Let6989586621679814851XsSym0 :: [a]) 
Break (p :: k1 ~> Bool) (x ': xs' :: [k1]) = Case_6989586621679814860 p x xs' (Let6989586621679814858Scrutinee_6989586621679811570Sym3 p x xs') 

sBreak :: forall a (t1 :: a ~> Bool) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) 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 (Apply (Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) t1) t2) Source #

Searching lists

type family NotElem (a1 :: a) (a2 :: t a) :: Bool where ... Source #

Equations

NotElem (x :: k1) (a_6989586621680390181 :: 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_6989586621680390181 

sNotElem :: forall a (t1 :: Type -> Type) (t2 :: a) (t3 :: t1 a). (SFoldable t1, SEq a) => Sing t2 -> Sing t3 -> Sing (Apply (Apply (NotElemSym0 :: TyFun a (t1 a ~> Bool) -> Type) 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 :: k1) ('(x, y) ': xys :: [(k1, k)]) = Case_6989586621679814753 key x y xys (Let6989586621679814751Scrutinee_6989586621679811584Sym4 key x y xys) 

sLookup :: forall a b (t1 :: a) (t2 :: [(a, b)]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) 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 (Apply (Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) 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 (Apply (Apply (Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) 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 (Apply (Apply (Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) 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 (Apply (Apply (Apply (Apply (ZipWith3Sym0 :: TyFun (a ~> (b ~> (c ~> d))) ([a] ~> ([b] ~> ([c] ~> [d]))) -> Type) 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) (Apply (Lambda_6989586621679815315Sym0 :: TyFun [(k2, k3)] (TyFun (k2, k3) (TyFun ([k2], [k3]) ([k2], [k3]) -> Type) -> Type) -> Type) xs)) (Apply (Apply (Tuple2Sym0 :: TyFun [k2] ([k3] ~> ([k2], [k3])) -> Type) (NilSym0 :: [k2])) (NilSym0 :: [k3]))) xs 

sUnzip :: forall a b (t :: [(a, b)]). Sing t -> Sing (Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) 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) (Apply (Lambda_6989586621679815297Sym0 :: TyFun [(k2, k3, k4)] (TyFun (k2, k3, k4) (TyFun ([k2], [k3], [k4]) ([k2], [k3], [k4]) -> Type) -> Type) -> Type) xs)) (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 (Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) 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 (Apply UnlinesSym0 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 (Let6989586621679815191GoSym2 w ws) ws) 

sUnwords :: forall (t :: [Symbol]). Sing t -> Sing (Apply UnwordsSym0 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) = Apply (Apply (Apply (ShowsPrec_6989586621680208728Sym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) arg) arg1) arg2

type Show_ (arg :: a) :: Symbol Source #

type Show_ (arg :: a) = Apply (Show__6989586621680208740Sym0 :: TyFun a Symbol -> Type) arg

type ShowList (arg :: [a]) (arg1 :: Symbol) :: Symbol Source #

type ShowList (arg :: [a]) (arg1 :: Symbol) = Apply (Apply (ShowList_6989586621680208748Sym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) arg) arg1

Instances

Instances details
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 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 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 (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 (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 (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 (NonEmpty a) Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Maybe a) Source # 
Instance details

Defined in Text.Show.Singletons

PShow [a] Source # 
Instance details

Defined in Text.Show.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 (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

default sShowsPrec :: forall (t1 :: Natural) (t2 :: a) (t3 :: Symbol). Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3 ~ Apply (Apply (Apply (ShowsPrec_6989586621680208728Sym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun a Symbol -> Type) t) Source #

default sShow_ :: forall (t :: a). Apply (Show_Sym0 :: TyFun a Symbol -> Type) t ~ Apply (Show__6989586621680208740Sym0 :: TyFun a Symbol -> Type) t => Sing t -> Sing (Apply (Show_Sym0 :: TyFun a Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

default sShowList :: forall (t1 :: [a]) (t2 :: Symbol). Apply (Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) t1) t2 ~ Apply (Apply (ShowList_6989586621680208748Sym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

Instances

Instances details
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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (All ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: All). Sing t -> Sing (Apply (Show_Sym0 :: TyFun All Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [All]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [All] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Any ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Any). Sing t -> Sing (Apply (Show_Sym0 :: TyFun Any Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Any]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Any] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Void ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Void). Sing t -> Sing (Apply (Show_Sym0 :: TyFun Void Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Void]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Void] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Ordering ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Ordering). Sing t -> Sing (Apply (Show_Sym0 :: TyFun Ordering Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Ordering]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Ordering] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Natural ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Natural). Sing t -> Sing (Apply (Show_Sym0 :: TyFun Natural Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Natural]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Natural] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (() ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: ()). Sing t -> Sing (Apply (Show_Sym0 :: TyFun () Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [()]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [()] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Bool ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Bool). Sing t -> Sing (Apply (Show_Sym0 :: TyFun Bool Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Bool]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Bool] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Char ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Char). Sing t -> Sing (Apply (Show_Sym0 :: TyFun Char Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Char]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Char] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Symbol ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Symbol). Sing t -> Sing (Apply (Show_Sym0 :: TyFun Symbol Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Symbol]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Symbol] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Identity a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Identity a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Identity a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Identity a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Identity a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (First a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: First a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (First a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [First a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Last a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Last a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Last a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Last a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (First a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: First a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (First a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [First a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Last a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Last a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Last a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Last a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Max a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Max a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Max a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Max a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Max a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Min a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Min a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Min a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Min a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Min a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (WrappedMonoid m ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: WrappedMonoid m). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (WrappedMonoid m) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [WrappedMonoid m]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [WrappedMonoid m] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Dual a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Dual a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Dual a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Dual a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Dual a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Product a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Product a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Product a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Product a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Product a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Sum a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Sum a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Sum a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Sum a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Sum a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (NonEmpty a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: NonEmpty a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (NonEmpty a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [NonEmpty a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [NonEmpty a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Maybe a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Maybe a). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Maybe a) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Maybe a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Maybe a] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ([a] ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: [a]). Sing t -> Sing (Apply (Show_Sym0 :: TyFun [a] Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [[a]]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [[a]] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Either a b ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Either a b). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Either a b) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Either a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Either a b] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Proxy s ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Proxy s). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Proxy s) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Proxy s]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Proxy s] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Arg a b ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Arg a b). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Arg a b) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Arg a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Arg a b] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: (a, b)). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (a, b) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [(a, b)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b)] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Const a b ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Const a b). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Const a b) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Const a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Const a b] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: (a, b, c)). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (a, b, c) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [(a, b, c)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c)] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c, d) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: (a, b, c, d)). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (a, b, c, d) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [(a, b, c, d)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c, d)] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c, d, e) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: (a, b, c, d, e)). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (a, b, c, d, e) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [(a, b, c, d, e)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c, d, e)] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c, d, e, f) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: (a, b, c, d, e, f)). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (a, b, c, d, e, f) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [(a, b, c, d, e, f)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c, d, e, f)] (Symbol ~> Symbol) -> Type) 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 (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c, d, e, f, g) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: (a, b, c, d, e, f, g)). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (a, b, c, d, e, f, g) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [(a, b, c, d, e, f, g)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c, d, e, f, g)] (Symbol ~> Symbol) -> Type) t1) t2) Source #

type family Shows (a1 :: a) (a2 :: Symbol) :: Symbol where ... Source #

Equations

Shows (s :: k1) a_6989586621680208701 = Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (k1 ~> (Symbol ~> Symbol)) -> Type) (FromInteger 0 :: Natural)) s) a_6989586621680208701 

sShows :: forall a (t1 :: a) (t2 :: Symbol). SShow a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) t1) t2) Source #

type family ShowChar (a :: Char) (a1 :: Symbol) :: Symbol where ... Source #

Equations

ShowChar a_6989586621680208673 a_6989586621680208675 = Apply (Apply ConsSymbolSym0 a_6989586621680208673) a_6989586621680208675 

sShowChar :: forall (t1 :: Char) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowCharSym0 t1) t2) Source #

type family ShowString (a :: Symbol) (a1 :: Symbol) :: Symbol where ... Source #

Equations

ShowString a_6989586621680208662 a_6989586621680208664 = Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) a_6989586621680208662) a_6989586621680208664 

sShowString :: forall (t1 :: Symbol) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowStringSym0 t1) t2) Source #

type family ShowParen (a :: Bool) (a1 :: Symbol ~> Symbol) (a2 :: Symbol) :: Symbol where ... Source #

Equations

ShowParen b p a_6989586621680208647 = Apply (Case_6989586621680208659 b p a_6989586621680208647 b) a_6989586621680208647 

sShowParen :: forall (t1 :: Bool) (t2 :: Symbol ~> Symbol) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowParenSym0 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) (a6989586621679133031 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym0 :: TyFun Bool (k ~> (k ~> k)) -> Type) (a6989586621679133031 :: Bool) = IfSym1 a6989586621679133031 :: TyFun k (k ~> k) -> Type

data IfSym1 (a6989586621679133031 :: 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 a6989586621679133031 :: TyFun k (k ~> k) -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym1 a6989586621679133031 :: TyFun k (k ~> k) -> Type) (a6989586621679133032 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym1 a6989586621679133031 :: TyFun k (k ~> k) -> Type) (a6989586621679133032 :: k) = IfSym2 a6989586621679133031 a6989586621679133032

data IfSym2 (a6989586621679133031 :: Bool) (a6989586621679133032 :: 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 a6989586621679133031 a6989586621679133032 :: TyFun k k -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym2 a6989586621679133031 a6989586621679133032 :: TyFun k k -> Type) (a6989586621679133033 :: k) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (IfSym2 a6989586621679133031 a6989586621679133032 :: TyFun k k -> Type) (a6989586621679133033 :: k) = If a6989586621679133031 a6989586621679133032 a6989586621679133033

type family IfSym3 (a6989586621679133031 :: Bool) (a6989586621679133032 :: k) (a6989586621679133033 :: k) :: k where ... Source #

Equations

IfSym3 a6989586621679133031 (a6989586621679133032 :: k) (a6989586621679133033 :: k) = If a6989586621679133031 a6989586621679133032 a6989586621679133033 

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 (&&@#@$) (a6989586621679132115 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (&&@#@$) (a6989586621679132115 :: Bool) = (&&@#@$$) a6989586621679132115

data (a6989586621679132115 :: 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 ((&&@#@$$) a6989586621679132115 :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((&&@#@$$) a6989586621679132115 :: TyFun Bool Bool -> Type) (a6989586621679132116 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((&&@#@$$) a6989586621679132115 :: TyFun Bool Bool -> Type) (a6989586621679132116 :: Bool) = a6989586621679132115 && a6989586621679132116

type family (a6989586621679132115 :: Bool) &&@#@$$$ (a6989586621679132116 :: Bool) :: Bool where ... infixr 3 Source #

Equations

a6989586621679132115 &&@#@$$$ a6989586621679132116 = a6989586621679132115 && a6989586621679132116 

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 (||@#@$) (a6989586621679132472 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply (||@#@$) (a6989586621679132472 :: Bool) = (||@#@$$) a6989586621679132472

data (a6989586621679132472 :: 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 ((||@#@$$) a6989586621679132472 :: TyFun Bool Bool -> Type) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((||@#@$$) a6989586621679132472 :: TyFun Bool Bool -> Type) (a6989586621679132473 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply ((||@#@$$) a6989586621679132472 :: TyFun Bool Bool -> Type) (a6989586621679132473 :: Bool) = a6989586621679132472 || a6989586621679132473

type family (a6989586621679132472 :: Bool) ||@#@$$$ (a6989586621679132473 :: Bool) :: Bool where ... infixr 2 Source #

Equations

a6989586621679132472 ||@#@$$$ a6989586621679132473 = a6989586621679132472 || a6989586621679132473 

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 (a6989586621679132813 :: Bool) Source # 
Instance details

Defined in Data.Bool.Singletons

type Apply NotSym0 (a6989586621679132813 :: Bool) = Not a6989586621679132813

type family NotSym1 (a6989586621679132813 :: Bool) :: Bool where ... Source #

Equations

NotSym1 a6989586621679132813 = Not a6989586621679132813 

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) (a6989586621679046214 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (JustSym0 :: TyFun a (Maybe a) -> Type) (a6989586621679046214 :: a) = 'Just a6989586621679046214

type family JustSym1 (a6989586621679046214 :: a) :: Maybe a where ... Source #

Equations

JustSym1 (a6989586621679046214 :: a) = 'Just a6989586621679046214 

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) (a6989586621679577734 :: b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym0 :: TyFun b ((a ~> b) ~> (Maybe a ~> b)) -> Type) (a6989586621679577734 :: b) = Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type

data Maybe_Sym1 (a6989586621679577734 :: 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 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679577735 :: a ~> b) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym1 a6989586621679577734 :: TyFun (a ~> b) (Maybe a ~> b) -> Type) (a6989586621679577735 :: a ~> b) = Maybe_Sym2 a6989586621679577734 a6989586621679577735

data Maybe_Sym2 (a6989586621679577734 :: b) (a6989586621679577735 :: 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 a6989586621679577734 a6989586621679577735 :: TyFun (Maybe a) b -> Type) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym2 a6989586621679577734 a6989586621679577735 :: TyFun (Maybe a) b -> Type) (a6989586621679577736 :: Maybe a) Source # 
Instance details

Defined in Data.Maybe.Singletons

type Apply (Maybe_Sym2 a6989586621679577734 a6989586621679577735 :: TyFun (Maybe a) b -> Type) (a6989586621679577736 :: Maybe a) = Maybe_ a6989586621679577734 a6989586621679577735 a6989586621679577736

type family Maybe_Sym3 (a6989586621679577734 :: b) (a6989586621679577735 :: a ~> b) (a6989586621679577736 :: Maybe a) :: b where ... Source #

Equations

Maybe_Sym3 (a6989586621679577734 :: b) (a6989586621679577735 :: a ~> b) (a6989586621679577736 :: Maybe a) = Maybe_ a6989586621679577734 a6989586621679577735 a6989586621679577736 

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) (a6989586621679046286 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (LeftSym0 :: TyFun a (Either a b) -> Type) (a6989586621679046286 :: a) = 'Left a6989586621679046286 :: Either a b

type family LeftSym1 (a6989586621679046286 :: a) :: Either a b where ... Source #

Equations

LeftSym1 (a6989586621679046286 :: a) = 'Left a6989586621679046286 :: 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) (a6989586621679046288 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (RightSym0 :: TyFun b (Either a b) -> Type) (a6989586621679046288 :: b) = 'Right a6989586621679046288 :: Either a b

type family RightSym1 (a6989586621679046288 :: b) :: Either a b where ... Source #

Equations

RightSym1 (a6989586621679046288 :: b) = 'Right a6989586621679046288 :: 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) (a6989586621679334944 :: a ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym0 :: TyFun (a ~> c) ((b ~> c) ~> (Either a b ~> c)) -> Type) (a6989586621679334944 :: a ~> c) = Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type

data Either_Sym1 (a6989586621679334944 :: 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 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679334945 :: b ~> c) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym1 a6989586621679334944 :: TyFun (b ~> c) (Either a b ~> c) -> Type) (a6989586621679334945 :: b ~> c) = Either_Sym2 a6989586621679334944 a6989586621679334945

data Either_Sym2 (a6989586621679334944 :: a ~> c) (a6989586621679334945 :: 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 a6989586621679334944 a6989586621679334945 :: TyFun (Either a b) c -> Type) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym2 a6989586621679334944 a6989586621679334945 :: TyFun (Either a b) c -> Type) (a6989586621679334946 :: Either a b) Source # 
Instance details

Defined in Data.Either.Singletons

type Apply (Either_Sym2 a6989586621679334944 a6989586621679334945 :: TyFun (Either a b) c -> Type) (a6989586621679334946 :: Either a b) = Either_ a6989586621679334944 a6989586621679334945 a6989586621679334946

type family Either_Sym3 (a6989586621679334944 :: a ~> c) (a6989586621679334945 :: b ~> c) (a6989586621679334946 :: Either a b) :: c where ... Source #

Equations

Either_Sym3 (a6989586621679334944 :: a ~> c) (a6989586621679334945 :: b ~> c) (a6989586621679334946 :: Either a b) = Either_ a6989586621679334944 a6989586621679334945 a6989586621679334946 

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) (a6989586621679046238 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$) :: TyFun a ([a] ~> [a]) -> Type) (a6989586621679046238 :: a) = (:@#@$$) a6989586621679046238

data (a6989586621679046238 :: 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 ((:@#@$$) a6989586621679046238 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$$) a6989586621679046238 :: TyFun [a] [a] -> Type) (a6989586621679046239 :: [a]) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply ((:@#@$$) a6989586621679046238 :: TyFun [a] [a] -> Type) (a6989586621679046239 :: [a]) = a6989586621679046238 ': a6989586621679046239

type family (a6989586621679046238 :: a) :@#@$$$ (a6989586621679046239 :: [a]) :: [a] where ... infixr 5 Source #

Equations

(a6989586621679046238 :: a) :@#@$$$ (a6989586621679046239 :: [a]) = a6989586621679046238 ': a6989586621679046239 

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) (a6989586621679046729 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym0 :: TyFun a (b ~> (a, b)) -> Type) (a6989586621679046729 :: a) = Tuple2Sym1 a6989586621679046729 :: TyFun b (a, b) -> Type

data Tuple2Sym1 (a6989586621679046729 :: 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 a6989586621679046729 :: TyFun b (a, b) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym1 a6989586621679046729 :: TyFun k2 (k1, k2) -> Type) (a6989586621679046730 :: k2) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple2Sym1 a6989586621679046729 :: TyFun k2 (k1, k2) -> Type) (a6989586621679046730 :: k2) = '(a6989586621679046729, a6989586621679046730)

type family Tuple2Sym2 (a6989586621679046729 :: a) (a6989586621679046730 :: b) :: (a, b) where ... Source #

Equations

Tuple2Sym2 (a6989586621679046729 :: k1) (a6989586621679046730 :: k2) = '(a6989586621679046729, a6989586621679046730) 

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) (a6989586621679046760 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym0 :: TyFun a (b ~> (c ~> (a, b, c))) -> Type) (a6989586621679046760 :: a) = Tuple3Sym1 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type

data Tuple3Sym1 (a6989586621679046760 :: 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 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym1 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679046761 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym1 a6989586621679046760 :: TyFun b (c ~> (a, b, c)) -> Type) (a6989586621679046761 :: b) = Tuple3Sym2 a6989586621679046760 a6989586621679046761 :: TyFun c (a, b, c) -> Type

data Tuple3Sym2 (a6989586621679046760 :: a) (a6989586621679046761 :: 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 a6989586621679046760 a6989586621679046761 :: TyFun c (a, b, c) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym2 a6989586621679046760 a6989586621679046761 :: TyFun k3 (k1, k2, k3) -> Type) (a6989586621679046762 :: k3) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple3Sym2 a6989586621679046760 a6989586621679046761 :: TyFun k3 (k1, k2, k3) -> Type) (a6989586621679046762 :: k3) = '(a6989586621679046760, a6989586621679046761, a6989586621679046762)

type family Tuple3Sym3 (a6989586621679046760 :: a) (a6989586621679046761 :: b) (a6989586621679046762 :: c) :: (a, b, c) where ... Source #

Equations

Tuple3Sym3 (a6989586621679046760 :: k1) (a6989586621679046761 :: k2) (a6989586621679046762 :: k3) = '(a6989586621679046760, a6989586621679046761, a6989586621679046762) 

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) (a6989586621679046809 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym0 :: TyFun a (b ~> (c ~> (d ~> (a, b, c, d)))) -> Type) (a6989586621679046809 :: a) = Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type

data Tuple4Sym1 (a6989586621679046809 :: 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 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679046810 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym1 a6989586621679046809 :: TyFun b (c ~> (d ~> (a, b, c, d))) -> Type) (a6989586621679046810 :: b) = Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type

data Tuple4Sym2 (a6989586621679046809 :: a) (a6989586621679046810 :: 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 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679046811 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym2 a6989586621679046809 a6989586621679046810 :: TyFun c (d ~> (a, b, c, d)) -> Type) (a6989586621679046811 :: c) = Tuple4Sym3 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: TyFun d (a, b, c, d) -> Type

data Tuple4Sym3 (a6989586621679046809 :: a) (a6989586621679046810 :: b) (a6989586621679046811 :: 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 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: TyFun d (a, b, c, d) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym3 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: TyFun k4 (k1, k2, k3, k4) -> Type) (a6989586621679046812 :: k4) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple4Sym3 a6989586621679046809 a6989586621679046810 a6989586621679046811 :: TyFun k4 (k1, k2, k3, k4) -> Type) (a6989586621679046812 :: k4) = '(a6989586621679046809, a6989586621679046810, a6989586621679046811, a6989586621679046812)

type family Tuple4Sym4 (a6989586621679046809 :: a) (a6989586621679046810 :: b) (a6989586621679046811 :: c) (a6989586621679046812 :: d) :: (a, b, c, d) where ... Source #

Equations

Tuple4Sym4 (a6989586621679046809 :: k1) (a6989586621679046810 :: k2) (a6989586621679046811 :: k3) (a6989586621679046812 :: k4) = '(a6989586621679046809, a6989586621679046810, a6989586621679046811, a6989586621679046812) 

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) (a6989586621679046878 :: 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) (a6989586621679046878 :: a) = Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type

data Tuple5Sym1 (a6989586621679046878 :: 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 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679046879 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym1 a6989586621679046878 :: TyFun b (c ~> (d ~> (e ~> (a, b, c, d, e)))) -> Type) (a6989586621679046879 :: b) = Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type

data Tuple5Sym2 (a6989586621679046878 :: a) (a6989586621679046879 :: 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 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679046880 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym2 a6989586621679046878 a6989586621679046879 :: TyFun c (d ~> (e ~> (a, b, c, d, e))) -> Type) (a6989586621679046880 :: c) = Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type

data Tuple5Sym3 (a6989586621679046878 :: a) (a6989586621679046879 :: b) (a6989586621679046880 :: 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 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679046881 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym3 a6989586621679046878 a6989586621679046879 a6989586621679046880 :: TyFun d (e ~> (a, b, c, d, e)) -> Type) (a6989586621679046881 :: d) = Tuple5Sym4 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun e (a, b, c, d, e) -> Type

data Tuple5Sym4 (a6989586621679046878 :: a) (a6989586621679046879 :: b) (a6989586621679046880 :: c) (a6989586621679046881 :: 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 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun e (a, b, c, d, e) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym4 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun k5 (k1, k2, k3, k4, k5) -> Type) (a6989586621679046882 :: k5) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple5Sym4 a6989586621679046878 a6989586621679046879 a6989586621679046880 a6989586621679046881 :: TyFun k5 (k1, k2, k3, k4, k5) -> Type) (a6989586621679046882 :: k5) = '(a6989586621679046878, a6989586621679046879, a6989586621679046880, a6989586621679046881, a6989586621679046882)

type family Tuple5Sym5 (a6989586621679046878 :: a) (a6989586621679046879 :: b) (a6989586621679046880 :: c) (a6989586621679046881 :: d) (a6989586621679046882 :: e) :: (a, b, c, d, e) where ... Source #

Equations

Tuple5Sym5 (a6989586621679046878 :: k1) (a6989586621679046879 :: k2) (a6989586621679046880 :: k3) (a6989586621679046881 :: k4) (a6989586621679046882 :: k5) = '(a6989586621679046878, a6989586621679046879, a6989586621679046880, a6989586621679046881, a6989586621679046882) 

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) (a6989586621679046969 :: 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) (a6989586621679046969 :: a) = Tuple6Sym1 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type

data Tuple6Sym1 (a6989586621679046969 :: 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 a6989586621679046969 :: 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 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679046970 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym1 a6989586621679046969 :: TyFun b (c ~> (d ~> (e ~> (f ~> (a, b, c, d, e, f))))) -> Type) (a6989586621679046970 :: b) = Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type

data Tuple6Sym2 (a6989586621679046969 :: a) (a6989586621679046970 :: 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 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679046971 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym2 a6989586621679046969 a6989586621679046970 :: TyFun c (d ~> (e ~> (f ~> (a, b, c, d, e, f)))) -> Type) (a6989586621679046971 :: c) = Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type

data Tuple6Sym3 (a6989586621679046969 :: a) (a6989586621679046970 :: b) (a6989586621679046971 :: 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 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679046972 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym3 a6989586621679046969 a6989586621679046970 a6989586621679046971 :: TyFun d (e ~> (f ~> (a, b, c, d, e, f))) -> Type) (a6989586621679046972 :: d) = Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type

data Tuple6Sym4 (a6989586621679046969 :: a) (a6989586621679046970 :: b) (a6989586621679046971 :: c) (a6989586621679046972 :: 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 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679046973 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym4 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 :: TyFun e (f ~> (a, b, c, d, e, f)) -> Type) (a6989586621679046973 :: e) = Tuple6Sym5 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun f (a, b, c, d, e, f) -> Type

data Tuple6Sym5 (a6989586621679046969 :: a) (a6989586621679046970 :: b) (a6989586621679046971 :: c) (a6989586621679046972 :: d) (a6989586621679046973 :: 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 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun f (a, b, c, d, e, f) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym5 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun k6 (k1, k2, k3, k4, k5, k6) -> Type) (a6989586621679046974 :: k6) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple6Sym5 a6989586621679046969 a6989586621679046970 a6989586621679046971 a6989586621679046972 a6989586621679046973 :: TyFun k6 (k1, k2, k3, k4, k5, k6) -> Type) (a6989586621679046974 :: k6) = '(a6989586621679046969, a6989586621679046970, a6989586621679046971, a6989586621679046972, a6989586621679046973, a6989586621679046974)

type family Tuple6Sym6 (a6989586621679046969 :: a) (a6989586621679046970 :: b) (a6989586621679046971 :: c) (a6989586621679046972 :: d) (a6989586621679046973 :: e) (a6989586621679046974 :: f) :: (a, b, c, d, e, f) where ... Source #

Equations

Tuple6Sym6 (a6989586621679046969 :: k1) (a6989586621679046970 :: k2) (a6989586621679046971 :: k3) (a6989586621679046972 :: k4) (a6989586621679046973 :: k5) (a6989586621679046974 :: k6) = '(a6989586621679046969, a6989586621679046970, a6989586621679046971, a6989586621679046972, a6989586621679046973, a6989586621679046974) 

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) (a6989586621679047084 :: 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) (a6989586621679047084 :: a) = Tuple7Sym1 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type

data Tuple7Sym1 (a6989586621679047084 :: 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 a6989586621679047084 :: 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 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679047085 :: b) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym1 a6989586621679047084 :: TyFun b (c ~> (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))))) -> Type) (a6989586621679047085 :: b) = Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type

data Tuple7Sym2 (a6989586621679047084 :: a) (a6989586621679047085 :: 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 a6989586621679047084 a6989586621679047085 :: 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 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679047086 :: c) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym2 a6989586621679047084 a6989586621679047085 :: TyFun c (d ~> (e ~> (f ~> (g ~> (a, b, c, d, e, f, g))))) -> Type) (a6989586621679047086 :: c) = Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type

data Tuple7Sym3 (a6989586621679047084 :: a) (a6989586621679047085 :: b) (a6989586621679047086 :: 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 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: 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 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679047087 :: d) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym3 a6989586621679047084 a6989586621679047085 a6989586621679047086 :: TyFun d (e ~> (f ~> (g ~> (a, b, c, d, e, f, g)))) -> Type) (a6989586621679047087 :: d) = Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type

data Tuple7Sym4 (a6989586621679047084 :: a) (a6989586621679047085 :: b) (a6989586621679047086 :: c) (a6989586621679047087 :: 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 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679047088 :: e) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym4 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 :: TyFun e (f ~> (g ~> (a, b, c, d, e, f, g))) -> Type) (a6989586621679047088 :: e) = Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type

data Tuple7Sym5 (a6989586621679047084 :: a) (a6989586621679047085 :: b) (a6989586621679047086 :: c) (a6989586621679047087 :: d) (a6989586621679047088 :: 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 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679047089 :: f) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym5 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 :: TyFun f (g ~> (a, b, c, d, e, f, g)) -> Type) (a6989586621679047089 :: f) = Tuple7Sym6 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun g (a, b, c, d, e, f, g) -> Type

data Tuple7Sym6 (a6989586621679047084 :: a) (a6989586621679047085 :: b) (a6989586621679047086 :: c) (a6989586621679047087 :: d) (a6989586621679047088 :: e) (a6989586621679047089 :: 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 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun g (a, b, c, d, e, f, g) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym6 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun k7 (k1, k2, k3, k4, k5, k6, k7) -> Type) (a6989586621679047090 :: k7) Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Apply (Tuple7Sym6 a6989586621679047084 a6989586621679047085 a6989586621679047086 a6989586621679047087 a6989586621679047088 a6989586621679047089 :: TyFun k7 (k1, k2, k3, k4, k5, k6, k7) -> Type) (a6989586621679047090 :: k7) = '(a6989586621679047084, a6989586621679047085, a6989586621679047086, a6989586621679047087, a6989586621679047088, a6989586621679047089, a6989586621679047090)

type family Tuple7Sym7 (a6989586621679047084 :: a) (a6989586621679047085 :: b) (a6989586621679047086 :: c) (a6989586621679047087 :: d) (a6989586621679047088 :: e) (a6989586621679047089 :: f) (a6989586621679047090 :: g) :: (a, b, c, d, e, f, g) where ... Source #

Equations

Tuple7Sym7 (a6989586621679047084 :: k1) (a6989586621679047085 :: k2) (a6989586621679047086 :: k3) (a6989586621679047087 :: k4) (a6989586621679047088 :: k5) (a6989586621679047089 :: k6) (a6989586621679047090 :: k7) = '(a6989586621679047084, a6989586621679047085, a6989586621679047086, a6989586621679047087, a6989586621679047088, a6989586621679047089, a6989586621679047090) 

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) (a6989586621679172905 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (FstSym0 :: TyFun (a, b) a -> Type) (a6989586621679172905 :: (a, b)) = Fst a6989586621679172905

type family FstSym1 (a6989586621679172905 :: (a, b)) :: a where ... Source #

Equations

FstSym1 (a6989586621679172905 :: (a, b)) = Fst a6989586621679172905 

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) (a6989586621679172901 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (SndSym0 :: TyFun (a, b) b -> Type) (a6989586621679172901 :: (a, b)) = Snd a6989586621679172901

type family SndSym1 (a6989586621679172901 :: (a, b)) :: b where ... Source #

Equations

SndSym1 (a6989586621679172901 :: (a, b)) = Snd a6989586621679172901 

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) (a6989586621679172893 :: (a, b) ~> c) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym0 :: TyFun ((a, b) ~> c) (a ~> (b ~> c)) -> Type) (a6989586621679172893 :: (a, b) ~> c) = CurrySym1 a6989586621679172893

data CurrySym1 (a6989586621679172893 :: (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 a6989586621679172893 :: TyFun a (b ~> c) -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym1 a6989586621679172893 :: TyFun a (b ~> c) -> Type) (a6989586621679172894 :: a) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym1 a6989586621679172893 :: TyFun a (b ~> c) -> Type) (a6989586621679172894 :: a) = CurrySym2 a6989586621679172893 a6989586621679172894

data CurrySym2 (a6989586621679172893 :: (a, b) ~> c) (a6989586621679172894 :: 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 a6989586621679172893 a6989586621679172894 :: TyFun b c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym2 a6989586621679172893 a6989586621679172894 :: TyFun b c -> Type) (a6989586621679172895 :: b) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (CurrySym2 a6989586621679172893 a6989586621679172894 :: TyFun b c -> Type) (a6989586621679172895 :: b) = Curry a6989586621679172893 a6989586621679172894 a6989586621679172895

type family CurrySym3 (a6989586621679172893 :: (a, b) ~> c) (a6989586621679172894 :: a) (a6989586621679172895 :: b) :: c where ... Source #

Equations

CurrySym3 (a6989586621679172893 :: (a, b) ~> c) (a6989586621679172894 :: a) (a6989586621679172895 :: b) = Curry a6989586621679172893 a6989586621679172894 a6989586621679172895 

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) (a6989586621679172885 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym0 :: TyFun (a ~> (b ~> c)) ((a, b) ~> c) -> Type) (a6989586621679172885 :: a ~> (b ~> c)) = UncurrySym1 a6989586621679172885

data UncurrySym1 (a6989586621679172885 :: 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 a6989586621679172885 :: TyFun (a, b) c -> Type) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym1 a6989586621679172885 :: TyFun (a, b) c -> Type) (a6989586621679172886 :: (a, b)) Source # 
Instance details

Defined in Data.Tuple.Singletons

type Apply (UncurrySym1 a6989586621679172885 :: TyFun (a, b) c -> Type) (a6989586621679172886 :: (a, b)) = Uncurry a6989586621679172885 a6989586621679172886

type family UncurrySym2 (a6989586621679172885 :: a ~> (b ~> c)) (a6989586621679172886 :: (a, b)) :: c where ... Source #

Equations

UncurrySym2 (a6989586621679172885 :: a ~> (b ~> c)) (a6989586621679172886 :: (a, b)) = Uncurry a6989586621679172885 a6989586621679172886 

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) (a6989586621679137918 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679137918 :: a) = (==@#@$$) a6989586621679137918

data (a6989586621679137918 :: 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 ((==@#@$$) a6989586621679137918 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$$) a6989586621679137918 :: TyFun a Bool -> Type) (a6989586621679137919 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((==@#@$$) a6989586621679137918 :: TyFun a Bool -> Type) (a6989586621679137919 :: a) = a6989586621679137918 == a6989586621679137919

type family (a6989586621679137918 :: a) ==@#@$$$ (a6989586621679137919 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679137918 :: a) ==@#@$$$ (a6989586621679137919 :: a) = a6989586621679137918 == a6989586621679137919 

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) (a6989586621679137923 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679137923 :: a) = (/=@#@$$) a6989586621679137923

data (a6989586621679137923 :: 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 ((/=@#@$$) a6989586621679137923 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$$) a6989586621679137923 :: TyFun a Bool -> Type) (a6989586621679137924 :: a) Source # 
Instance details

Defined in Data.Eq.Singletons

type Apply ((/=@#@$$) a6989586621679137923 :: TyFun a Bool -> Type) (a6989586621679137924 :: a) = a6989586621679137923 /= a6989586621679137924

type family (a6989586621679137923 :: a) /=@#@$$$ (a6989586621679137924 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679137923 :: a) /=@#@$$$ (a6989586621679137924 :: a) = a6989586621679137923 /= a6989586621679137924 

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) (a6989586621679237108 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym0 :: TyFun a (a ~> Ordering) -> Type) (a6989586621679237108 :: a) = CompareSym1 a6989586621679237108

data CompareSym1 (a6989586621679237108 :: 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 a6989586621679237108 :: TyFun a Ordering -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym1 a6989586621679237108 :: TyFun a Ordering -> Type) (a6989586621679237109 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (CompareSym1 a6989586621679237108 :: TyFun a Ordering -> Type) (a6989586621679237109 :: a) = Compare a6989586621679237108 a6989586621679237109

type family CompareSym2 (a6989586621679237108 :: a) (a6989586621679237109 :: a) :: Ordering where ... Source #

Equations

CompareSym2 (a6989586621679237108 :: a) (a6989586621679237109 :: a) = Compare a6989586621679237108 a6989586621679237109 

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) (a6989586621679237113 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679237113 :: a) = (<@#@$$) a6989586621679237113

data (a6989586621679237113 :: 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 ((<@#@$$) a6989586621679237113 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$$) a6989586621679237113 :: TyFun a Bool -> Type) (a6989586621679237114 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<@#@$$) a6989586621679237113 :: TyFun a Bool -> Type) (a6989586621679237114 :: a) = a6989586621679237113 < a6989586621679237114

type family (a6989586621679237113 :: a) <@#@$$$ (a6989586621679237114 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679237113 :: a) <@#@$$$ (a6989586621679237114 :: a) = a6989586621679237113 < a6989586621679237114 

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) (a6989586621679237118 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679237118 :: a) = (<=@#@$$) a6989586621679237118

data (a6989586621679237118 :: 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 ((<=@#@$$) a6989586621679237118 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$$) a6989586621679237118 :: TyFun a Bool -> Type) (a6989586621679237119 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((<=@#@$$) a6989586621679237118 :: TyFun a Bool -> Type) (a6989586621679237119 :: a) = a6989586621679237118 <= a6989586621679237119

type family (a6989586621679237118 :: a) <=@#@$$$ (a6989586621679237119 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679237118 :: a) <=@#@$$$ (a6989586621679237119 :: a) = a6989586621679237118 <= a6989586621679237119 

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) (a6989586621679237123 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679237123 :: a) = (>@#@$$) a6989586621679237123

data (a6989586621679237123 :: 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 ((>@#@$$) a6989586621679237123 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$$) a6989586621679237123 :: TyFun a Bool -> Type) (a6989586621679237124 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>@#@$$) a6989586621679237123 :: TyFun a Bool -> Type) (a6989586621679237124 :: a) = a6989586621679237123 > a6989586621679237124

type family (a6989586621679237123 :: a) >@#@$$$ (a6989586621679237124 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679237123 :: a) >@#@$$$ (a6989586621679237124 :: a) = a6989586621679237123 > a6989586621679237124 

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) (a6989586621679237128 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$) :: TyFun a (a ~> Bool) -> Type) (a6989586621679237128 :: a) = (>=@#@$$) a6989586621679237128

data (a6989586621679237128 :: 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 ((>=@#@$$) a6989586621679237128 :: TyFun a Bool -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$$) a6989586621679237128 :: TyFun a Bool -> Type) (a6989586621679237129 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply ((>=@#@$$) a6989586621679237128 :: TyFun a Bool -> Type) (a6989586621679237129 :: a) = a6989586621679237128 >= a6989586621679237129

type family (a6989586621679237128 :: a) >=@#@$$$ (a6989586621679237129 :: a) :: Bool where ... infix 4 Source #

Equations

(a6989586621679237128 :: a) >=@#@$$$ (a6989586621679237129 :: a) = a6989586621679237128 >= a6989586621679237129 

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) (a6989586621679237133 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679237133 :: a) = MaxSym1 a6989586621679237133

data MaxSym1 (a6989586621679237133 :: 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 a6989586621679237133 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym1 a6989586621679237133 :: TyFun a a -> Type) (a6989586621679237134 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MaxSym1 a6989586621679237133 :: TyFun a a -> Type) (a6989586621679237134 :: a) = Max a6989586621679237133 a6989586621679237134

type family MaxSym2 (a6989586621679237133 :: a) (a6989586621679237134 :: a) :: a where ... Source #

Equations

MaxSym2 (a6989586621679237133 :: a) (a6989586621679237134 :: a) = Max a6989586621679237133 a6989586621679237134 

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) (a6989586621679237138 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679237138 :: a) = MinSym1 a6989586621679237138

data MinSym1 (a6989586621679237138 :: 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 a6989586621679237138 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym1 a6989586621679237138 :: TyFun a a -> Type) (a6989586621679237139 :: a) Source # 
Instance details

Defined in Data.Ord.Singletons

type Apply (MinSym1 a6989586621679237138 :: TyFun a a -> Type) (a6989586621679237139 :: a) = Min a6989586621679237138 a6989586621679237139

type family MinSym2 (a6989586621679237138 :: a) (a6989586621679237139 :: a) :: a where ... Source #

Equations

MinSym2 (a6989586621679237138 :: a) (a6989586621679237139 :: a) = Min a6989586621679237138 a6989586621679237139 

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 k2 -> Type) (a6989586621679612929 :: Natural) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (ToEnumSym0 :: TyFun Natural k2 -> Type) (a6989586621679612929 :: Natural) = ToEnum a6989586621679612929 :: k2

type family ToEnumSym1 (a6989586621679612929 :: Natural) :: a where ... Source #

Equations

ToEnumSym1 a6989586621679612929 = ToEnum a6989586621679612929 :: 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) (a6989586621679612932 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (FromEnumSym0 :: TyFun a Natural -> Type) (a6989586621679612932 :: a) = FromEnum a6989586621679612932

type family FromEnumSym1 (a6989586621679612932 :: a) :: Natural where ... Source #

Equations

FromEnumSym1 (a6989586621679612932 :: a) = FromEnum a6989586621679612932 

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) (a6989586621679612936 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679612936 :: a) = EnumFromToSym1 a6989586621679612936

data EnumFromToSym1 (a6989586621679612936 :: 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 a6989586621679612936 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym1 a6989586621679612936 :: TyFun a [a] -> Type) (a6989586621679612937 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym1 a6989586621679612936 :: TyFun a [a] -> Type) (a6989586621679612937 :: a) = EnumFromTo a6989586621679612936 a6989586621679612937

type family EnumFromToSym2 (a6989586621679612936 :: a) (a6989586621679612937 :: a) :: [a] where ... Source #

Equations

EnumFromToSym2 (a6989586621679612936 :: a) (a6989586621679612937 :: a) = EnumFromTo a6989586621679612936 a6989586621679612937 

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) (a6989586621679612942 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679612942 :: a) = EnumFromThenToSym1 a6989586621679612942

data EnumFromThenToSym1 (a6989586621679612942 :: 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 a6989586621679612942 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679612942 :: TyFun a (a ~> [a]) -> Type) (a6989586621679612943 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679612942 :: TyFun a (a ~> [a]) -> Type) (a6989586621679612943 :: a) = EnumFromThenToSym2 a6989586621679612942 a6989586621679612943

data EnumFromThenToSym2 (a6989586621679612942 :: a) (a6989586621679612943 :: 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 a6989586621679612942 a6989586621679612943 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym2 a6989586621679612942 a6989586621679612943 :: TyFun a [a] -> Type) (a6989586621679612944 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym2 a6989586621679612942 a6989586621679612943 :: TyFun a [a] -> Type) (a6989586621679612944 :: a) = EnumFromThenTo a6989586621679612942 a6989586621679612943 a6989586621679612944

type family EnumFromThenToSym3 (a6989586621679612942 :: a) (a6989586621679612943 :: a) (a6989586621679612944 :: a) :: [a] where ... Source #

Equations

EnumFromThenToSym3 (a6989586621679612942 :: a) (a6989586621679612943 :: a) (a6989586621679612944 :: a) = EnumFromThenTo a6989586621679612942 a6989586621679612943 a6989586621679612944 

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) (a6989586621679590942 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679590942 :: a) = (+@#@$$) a6989586621679590942

data (a6989586621679590942 :: 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 ((+@#@$$) a6989586621679590942 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$$) a6989586621679590942 :: TyFun a a -> Type) (a6989586621679590943 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((+@#@$$) a6989586621679590942 :: TyFun a a -> Type) (a6989586621679590943 :: a) = a6989586621679590942 + a6989586621679590943

type family (a6989586621679590942 :: a) +@#@$$$ (a6989586621679590943 :: a) :: a where ... infixl 6 Source #

Equations

(a6989586621679590942 :: a) +@#@$$$ (a6989586621679590943 :: a) = a6989586621679590942 + a6989586621679590943 

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) (a6989586621679590947 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

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

data (a6989586621679590947 :: 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 ((-@#@$$) a6989586621679590947 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$$) a6989586621679590947 :: TyFun a a -> Type) (a6989586621679590948 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((-@#@$$) a6989586621679590947 :: TyFun a a -> Type) (a6989586621679590948 :: a) = a6989586621679590947 - a6989586621679590948

type family (a6989586621679590947 :: a) -@#@$$$ (a6989586621679590948 :: a) :: a where ... infixl 6 Source #

Equations

(a6989586621679590947 :: a) -@#@$$$ (a6989586621679590948 :: a) = a6989586621679590947 - a6989586621679590948 

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) (a6989586621679590952 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679590952 :: a) = (*@#@$$) a6989586621679590952

data (a6989586621679590952 :: 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 ((*@#@$$) a6989586621679590952 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$$) a6989586621679590952 :: TyFun a a -> Type) (a6989586621679590953 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply ((*@#@$$) a6989586621679590952 :: TyFun a a -> Type) (a6989586621679590953 :: a) = a6989586621679590952 * a6989586621679590953

type family (a6989586621679590952 :: a) *@#@$$$ (a6989586621679590953 :: a) :: a where ... infixl 7 Source #

Equations

(a6989586621679590952 :: a) *@#@$$$ (a6989586621679590953 :: a) = a6989586621679590952 * a6989586621679590953 

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) (a6989586621679590956 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (NegateSym0 :: TyFun a a -> Type) (a6989586621679590956 :: a) = Negate a6989586621679590956

type family NegateSym1 (a6989586621679590956 :: a) :: a where ... Source #

Equations

NegateSym1 (a6989586621679590956 :: a) = Negate a6989586621679590956 

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) (a6989586621679590959 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (AbsSym0 :: TyFun a a -> Type) (a6989586621679590959 :: a) = Abs a6989586621679590959

type family AbsSym1 (a6989586621679590959 :: a) :: a where ... Source #

Equations

AbsSym1 (a6989586621679590959 :: a) = Abs a6989586621679590959 

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) (a6989586621679590962 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SignumSym0 :: TyFun a a -> Type) (a6989586621679590962 :: a) = Signum a6989586621679590962

type family SignumSym1 (a6989586621679590962 :: a) :: a where ... Source #

Equations

SignumSym1 (a6989586621679590962 :: a) = Signum a6989586621679590962 

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 k2 -> Type) (a6989586621679590965 :: Natural) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (FromIntegerSym0 :: TyFun Natural k2 -> Type) (a6989586621679590965 :: Natural) = FromInteger a6989586621679590965 :: k2

type family FromIntegerSym1 (a6989586621679590965 :: Natural) :: a where ... Source #

Equations

FromIntegerSym1 a6989586621679590965 = FromInteger a6989586621679590965 :: 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) (a6989586621679590935 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679590935 :: a) = SubtractSym1 a6989586621679590935

data SubtractSym1 (a6989586621679590935 :: 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 a6989586621679590935 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym1 a6989586621679590935 :: TyFun a a -> Type) (a6989586621679590936 :: a) Source # 
Instance details

Defined in GHC.Num.Singletons

type Apply (SubtractSym1 a6989586621679590935 :: TyFun a a -> Type) (a6989586621679590936 :: a) = Subtract a6989586621679590935 a6989586621679590936

type family SubtractSym2 (a6989586621679590935 :: a) (a6989586621679590936 :: a) :: a where ... Source #

Equations

SubtractSym2 (a6989586621679590935 :: a) (a6989586621679590936 :: a) = Subtract a6989586621679590935 a6989586621679590936 

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) (a6989586621679207889 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679207889 :: a) = (<>@#@$$) a6989586621679207889

data (a6989586621679207889 :: 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 ((<>@#@$$) a6989586621679207889 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$$) a6989586621679207889 :: TyFun a a -> Type) (a6989586621679207890 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$$) a6989586621679207889 :: TyFun a a -> Type) (a6989586621679207890 :: a) = a6989586621679207889 <> a6989586621679207890

type family (a6989586621679207889 :: a) <>@#@$$$ (a6989586621679207890 :: a) :: a where ... infixr 6 Source #

Equations

(a6989586621679207889 :: a) <>@#@$$$ (a6989586621679207890 :: a) = a6989586621679207889 <> a6989586621679207890 

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) (a6989586621680292326 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621680292326 :: a) = MappendSym1 a6989586621680292326

data MappendSym1 (a6989586621680292326 :: 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 a6989586621680292326 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym1 a6989586621680292326 :: TyFun a a -> Type) (a6989586621680292327 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym1 a6989586621680292326 :: TyFun a a -> Type) (a6989586621680292327 :: a) = Mappend a6989586621680292326 a6989586621680292327

type family MappendSym2 (a6989586621680292326 :: a) (a6989586621680292327 :: a) :: a where ... Source #

Equations

MappendSym2 (a6989586621680292326 :: a) (a6989586621680292327 :: a) = Mappend a6989586621680292326 a6989586621680292327 

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) (a6989586621680292330 :: [a]) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621680292330 :: [a]) = Mconcat a6989586621680292330

type family MconcatSym1 (a6989586621680292330 :: [a]) :: a where ... Source #

Equations

MconcatSym1 (a6989586621680292330 :: [a]) = Mconcat a6989586621680292330 

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) (a6989586621679348484 :: a ~> b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym0 :: TyFun (a ~> b) (f a ~> f b) -> Type) (a6989586621679348484 :: a ~> b) = FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type

data FmapSym1 (a6989586621679348484 :: 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 a6989586621679348484 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type) (a6989586621679348485 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (FmapSym1 a6989586621679348484 :: TyFun (f a) (f b) -> Type) (a6989586621679348485 :: f a) = Fmap a6989586621679348484 a6989586621679348485

type family FmapSym2 (a6989586621679348484 :: a ~> b) (a6989586621679348485 :: f a) :: f b where ... Source #

Equations

FmapSym2 (a6989586621679348484 :: a ~> b) (a6989586621679348485 :: f a) = Fmap a6989586621679348484 a6989586621679348485 

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) (a6989586621679348489 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

data (a6989586621679348489 :: 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 ((<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<$@#@$$) a6989586621679348489 :: TyFun (f b) (f a) -> Type) (a6989586621679348490 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

type family (a6989586621679348489 :: a) <$@#@$$$ (a6989586621679348490 :: f b) :: f a where ... infixl 4 Source #

Equations

(a6989586621679348489 :: a) <$@#@$$$ (a6989586621679348490 :: f b) = a6989586621679348489 <$ a6989586621679348490 

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) (a6989586621679532919 :: a ~> b) Source # 
Instance details

Defined in Data.Functor.Singletons

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

data (a6989586621679532919 :: 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 ((<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Data.Functor.Singletons

type Apply ((<$>@#@$$) a6989586621679532919 :: TyFun (f a) (f b) -> Type) (a6989586621679532920 :: f a) Source # 
Instance details

Defined in Data.Functor.Singletons

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

type family (a6989586621679532919 :: a ~> b) <$>@#@$$$ (a6989586621679532920 :: f a) :: f b where ... infixl 4 Source #

Equations

(a6989586621679532919 :: a ~> b) <$>@#@$$$ (a6989586621679532920 :: f a) = a6989586621679532919 <$> a6989586621679532920 

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) (a6989586621679348508 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (PureSym0 :: TyFun a (f a) -> Type) (a6989586621679348508 :: a) = Pure a6989586621679348508 :: f a

type family PureSym1 (a6989586621679348508 :: a) :: f a where ... Source #

Equations

PureSym1 (a6989586621679348508 :: a) = Pure a6989586621679348508 :: 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) (a6989586621679348512 :: f (a ~> b)) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

data (a6989586621679348512 :: 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 ((<*>@#@$$) a6989586621679348512 :: TyFun (f a) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$$) a6989586621679348512 :: TyFun (f a) (f b) -> Type) (a6989586621679348513 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*>@#@$$) a6989586621679348512 :: TyFun (f a) (f b) -> Type) (a6989586621679348513 :: f a) = a6989586621679348512 <*> a6989586621679348513

type family (a6989586621679348512 :: f (a ~> b)) <*>@#@$$$ (a6989586621679348513 :: f a) :: f b where ... infixl 4 Source #

Equations

(a6989586621679348512 :: f (a ~> b)) <*>@#@$$$ (a6989586621679348513 :: f a) = a6989586621679348512 <*> a6989586621679348513 

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) (a6989586621679348524 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

data (a6989586621679348524 :: 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 ((*>@#@$$) a6989586621679348524 :: TyFun (f b) (f b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$$) a6989586621679348524 :: TyFun (f b) (f b) -> Type) (a6989586621679348525 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((*>@#@$$) a6989586621679348524 :: TyFun (f b) (f b) -> Type) (a6989586621679348525 :: f b) = a6989586621679348524 *> a6989586621679348525

type family (a6989586621679348524 :: f a) *>@#@$$$ (a6989586621679348525 :: f b) :: f b where ... infixl 4 Source #

Equations

(a6989586621679348524 :: f a) *>@#@$$$ (a6989586621679348525 :: f b) = a6989586621679348524 *> a6989586621679348525 

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) (a6989586621679348529 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

data (a6989586621679348529 :: 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 ((<*@#@$$) a6989586621679348529 :: TyFun (f b) (f a) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$$) a6989586621679348529 :: TyFun (f b) (f a) -> Type) (a6989586621679348530 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((<*@#@$$) a6989586621679348529 :: TyFun (f b) (f a) -> Type) (a6989586621679348530 :: f b) = a6989586621679348529 <* a6989586621679348530

type family (a6989586621679348529 :: f a) <*@#@$$$ (a6989586621679348530 :: f b) :: f a where ... infixl 4 Source #

Equations

(a6989586621679348529 :: f a) <*@#@$$$ (a6989586621679348530 :: f b) = a6989586621679348529 <* a6989586621679348530 

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) (a6989586621679348518 :: 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) (a6989586621679348518 :: a ~> (b ~> c)) = LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type

data LiftA2Sym1 (a6989586621679348518 :: 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 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679348519 :: f a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym1 a6989586621679348518 :: TyFun (f a) (f b ~> f c) -> Type) (a6989586621679348519 :: f a) = LiftA2Sym2 a6989586621679348518 a6989586621679348519

data LiftA2Sym2 (a6989586621679348518 :: a ~> (b ~> c)) (a6989586621679348519 :: 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 a6989586621679348518 a6989586621679348519 :: TyFun (f b) (f c) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym2 a6989586621679348518 a6989586621679348519 :: TyFun (f b) (f c) -> Type) (a6989586621679348520 :: f b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (LiftA2Sym2 a6989586621679348518 a6989586621679348519 :: TyFun (f b) (f c) -> Type) (a6989586621679348520 :: f b) = LiftA2 a6989586621679348518 a6989586621679348519 a6989586621679348520

type family LiftA2Sym3 (a6989586621679348518 :: a ~> (b ~> c)) (a6989586621679348519 :: f a) (a6989586621679348520 :: f b) :: f c where ... Source #

Equations

LiftA2Sym3 (a6989586621679348518 :: a ~> (b ~> c)) (a6989586621679348519 :: f a) (a6989586621679348520 :: f b) = LiftA2 a6989586621679348518 a6989586621679348519 a6989586621679348520 

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) (a6989586621679348592 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

data (a6989586621679348592 :: 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 ((>>=@#@$$) a6989586621679348592 :: TyFun (a ~> m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>=@#@$$) a6989586621679348592 :: TyFun (a ~> m b) (m b) -> Type) (a6989586621679348593 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

type family (a6989586621679348592 :: m a) >>=@#@$$$ (a6989586621679348593 :: a ~> m b) :: m b where ... infixl 1 Source #

Equations

(a6989586621679348592 :: m a) >>=@#@$$$ (a6989586621679348593 :: a ~> m b) = a6989586621679348592 >>= a6989586621679348593 

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) (a6989586621679348597 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

data (a6989586621679348597 :: 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 ((>>@#@$$) a6989586621679348597 :: TyFun (m b) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$$) a6989586621679348597 :: TyFun (m b) (m b) -> Type) (a6989586621679348598 :: m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((>>@#@$$) a6989586621679348597 :: TyFun (m b) (m b) -> Type) (a6989586621679348598 :: m b) = a6989586621679348597 >> a6989586621679348598

type family (a6989586621679348597 :: m a) >>@#@$$$ (a6989586621679348598 :: m b) :: m b where ... infixl 1 Source #

Equations

(a6989586621679348597 :: m a) >>@#@$$$ (a6989586621679348598 :: m b) = a6989586621679348597 >> a6989586621679348598 

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) (a6989586621679348601 :: a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply (ReturnSym0 :: TyFun a (m a) -> Type) (a6989586621679348601 :: a) = Return a6989586621679348601 :: m a

type family ReturnSym1 (a6989586621679348601 :: a) :: m a where ... Source #

Equations

ReturnSym1 (a6989586621679348601 :: a) = Return a6989586621679348601 :: 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) (a6989586621679549513 :: [Char]) Source # 
Instance details

Defined in Control.Monad.Fail.Singletons

type Apply (FailSym0 :: TyFun [Char] (m a) -> Type) (a6989586621679549513 :: [Char]) = Fail a6989586621679549513 :: m a

type family FailSym1 (a6989586621679549513 :: [Char]) :: m a where ... Source #

Equations

FailSym1 a6989586621679549513 = Fail a6989586621679549513 :: 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) (a6989586621680390321 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621680390321 :: a ~> m b) = MapM_Sym1 a6989586621680390321 :: TyFun (t a) (m ()) -> Type

data MapM_Sym1 (a6989586621680390321 :: 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 a6989586621680390321 :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym1 a6989586621680390321 :: TyFun (t a) (m ()) -> Type) (a6989586621680390322 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym1 a6989586621680390321 :: TyFun (t a) (m ()) -> Type) (a6989586621680390322 :: t a) = MapM_ a6989586621680390321 a6989586621680390322

type family MapM_Sym2 (a6989586621680390321 :: a ~> m b) (a6989586621680390322 :: t a) :: m () where ... Source #

Equations

MapM_Sym2 (a6989586621680390321 :: a ~> m b) (a6989586621680390322 :: t a) = MapM_ a6989586621680390321 a6989586621680390322 

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) (a6989586621680390297 :: t (m a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621680390297 :: t (m a)) = Sequence_ a6989586621680390297

type family Sequence_Sym1 (a6989586621680390297 :: t (m a)) :: m () where ... Source #

Equations

Sequence_Sym1 (a6989586621680390297 :: t (m a)) = Sequence_ a6989586621680390297 

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) (a6989586621679348437 :: a ~> m b) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

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

data (a6989586621679348437 :: 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 ((=<<@#@$$) a6989586621679348437 :: TyFun (m a) (m b) -> Type) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$$) a6989586621679348437 :: TyFun (m a) (m b) -> Type) (a6989586621679348438 :: m a) Source # 
Instance details

Defined in Control.Monad.Singletons.Internal

type Apply ((=<<@#@$$) a6989586621679348437 :: TyFun (m a) (m b) -> Type) (a6989586621679348438 :: m a) = a6989586621679348437 =<< a6989586621679348438

type family (a6989586621679348437 :: a ~> m b) =<<@#@$$$ (a6989586621679348438 :: m a) :: m b where ... infixr 1 Source #

Equations

(a6989586621679348437 :: a ~> m b) =<<@#@$$$ (a6989586621679348438 :: m a) = a6989586621679348437 =<< a6989586621679348438 

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) (a6989586621680390439 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680390439 :: a) = ElemSym1 a6989586621680390439 :: TyFun (t a) Bool -> Type

data ElemSym1 (a6989586621680390439 :: 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 a6989586621680390439 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621680390439 :: TyFun (t a) Bool -> Type) (a6989586621680390440 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621680390439 :: TyFun (t a) Bool -> Type) (a6989586621680390440 :: t a) = Elem a6989586621680390439 a6989586621680390440

type family ElemSym2 (a6989586621680390439 :: a) (a6989586621680390440 :: t a) :: Bool where ... Source #

Equations

ElemSym2 (a6989586621680390439 :: a) (a6989586621680390440 :: t a) = Elem a6989586621680390439 a6989586621680390440 

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) (a6989586621680390387 :: a ~> m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680390387 :: a ~> m) = FoldMapSym1 a6989586621680390387 :: TyFun (t a) m -> Type

data FoldMapSym1 (a6989586621680390387 :: 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 a6989586621680390387 :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym1 a6989586621680390387 :: TyFun (t a) m -> Type) (a6989586621680390388 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym1 a6989586621680390387 :: TyFun (t a) m -> Type) (a6989586621680390388 :: t a) = FoldMap a6989586621680390387 a6989586621680390388

type family FoldMapSym2 (a6989586621680390387 :: a ~> m) (a6989586621680390388 :: t a) :: m where ... Source #

Equations

FoldMapSym2 (a6989586621680390387 :: a ~> m) (a6989586621680390388 :: t a) = FoldMap a6989586621680390387 a6989586621680390388 

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) (a6989586621680390393 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390393 :: a ~> (b ~> b)) = FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type

data FoldrSym1 (a6989586621680390393 :: 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 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) (a6989586621680390394 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621680390393 :: TyFun b (t a ~> b) -> Type) (a6989586621680390394 :: b) = FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type

data FoldrSym2 (a6989586621680390393 :: a ~> (b ~> b)) (a6989586621680390394 :: 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 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type) (a6989586621680390395 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym2 a6989586621680390393 a6989586621680390394 :: TyFun (t a) b -> Type) (a6989586621680390395 :: t a) = Foldr a6989586621680390393 a6989586621680390394 a6989586621680390395

type family FoldrSym3 (a6989586621680390393 :: a ~> (b ~> b)) (a6989586621680390394 :: b) (a6989586621680390395 :: t a) :: b where ... Source #

Equations

FoldrSym3 (a6989586621680390393 :: a ~> (b ~> b)) (a6989586621680390394 :: b) (a6989586621680390395 :: t a) = Foldr a6989586621680390393 a6989586621680390394 a6989586621680390395 

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) (a6989586621680390407 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680390407 :: b ~> (a ~> b)) = FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type

data FoldlSym1 (a6989586621680390407 :: 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 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) (a6989586621680390408 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621680390407 :: TyFun b (t a ~> b) -> Type) (a6989586621680390408 :: b) = FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type

data FoldlSym2 (a6989586621680390407 :: b ~> (a ~> b)) (a6989586621680390408 :: 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 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type) (a6989586621680390409 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym2 a6989586621680390407 a6989586621680390408 :: TyFun (t a) b -> Type) (a6989586621680390409 :: t a) = Foldl a6989586621680390407 a6989586621680390408 a6989586621680390409

type family FoldlSym3 (a6989586621680390407 :: b ~> (a ~> b)) (a6989586621680390408 :: b) (a6989586621680390409 :: t a) :: b where ... Source #

Equations

FoldlSym3 (a6989586621680390407 :: b ~> (a ~> b)) (a6989586621680390408 :: b) (a6989586621680390409 :: t a) = Foldl a6989586621680390407 a6989586621680390408 a6989586621680390409 

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) (a6989586621680390420 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390420 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type

data Foldr1Sym1 (a6989586621680390420 :: 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 a6989586621680390420 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type) (a6989586621680390421 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym1 a6989586621680390420 :: TyFun (t a) a -> Type) (a6989586621680390421 :: t a) = Foldr1 a6989586621680390420 a6989586621680390421

type family Foldr1Sym2 (a6989586621680390420 :: a ~> (a ~> a)) (a6989586621680390421 :: t a) :: a where ... Source #

Equations

Foldr1Sym2 (a6989586621680390420 :: a ~> (a ~> a)) (a6989586621680390421 :: t a) = Foldr1 a6989586621680390420 a6989586621680390421 

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) (a6989586621680390425 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680390425 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type

data Foldl1Sym1 (a6989586621680390425 :: 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 a6989586621680390425 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type) (a6989586621680390426 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym1 a6989586621680390425 :: TyFun (t a) a -> Type) (a6989586621680390426 :: t a) = Foldl1 a6989586621680390425 a6989586621680390426

type family Foldl1Sym2 (a6989586621680390425 :: a ~> (a ~> a)) (a6989586621680390426 :: t a) :: a where ... Source #

Equations

Foldl1Sym2 (a6989586621680390425 :: a ~> (a ~> a)) (a6989586621680390426 :: t a) = Foldl1 a6989586621680390425 a6989586621680390426 

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) (a6989586621680390443 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680390443 :: t a) = Maximum a6989586621680390443

type family MaximumSym1 (a6989586621680390443 :: t a) :: a where ... Source #

Equations

MaximumSym1 (a6989586621680390443 :: t a) = Maximum a6989586621680390443 

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) (a6989586621680390446 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680390446 :: t a) = Minimum a6989586621680390446

type family MinimumSym1 (a6989586621680390446 :: t a) :: a where ... Source #

Equations

MinimumSym1 (a6989586621680390446 :: t a) = Minimum a6989586621680390446 

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) (a6989586621680390452 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680390452 :: t a) = Product a6989586621680390452

type family ProductSym1 (a6989586621680390452 :: t a) :: a where ... Source #

Equations

ProductSym1 (a6989586621680390452 :: t a) = Product a6989586621680390452 

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) (a6989586621680390449 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621680390449 :: t a) = Sum a6989586621680390449

type family SumSym1 (a6989586621680390449 :: t a) :: a where ... Source #

Equations

SumSym1 (a6989586621680390449 :: t a) = Sum a6989586621680390449 

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) (a6989586621680733986 :: a ~> f b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym0 :: TyFun (a ~> f b) (t a ~> f (t b)) -> Type) (a6989586621680733986 :: a ~> f b) = TraverseSym1 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type

data TraverseSym1 (a6989586621680733986 :: 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 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym1 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680733987 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (TraverseSym1 a6989586621680733986 :: TyFun (t a) (f (t b)) -> Type) (a6989586621680733987 :: t a) = Traverse a6989586621680733986 a6989586621680733987

type family TraverseSym2 (a6989586621680733986 :: a ~> f b) (a6989586621680733987 :: t a) :: f (t b) where ... Source #

Equations

TraverseSym2 (a6989586621680733986 :: a ~> f b) (a6989586621680733987 :: t a) = Traverse a6989586621680733986 a6989586621680733987 

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) (a6989586621680733990 :: t (f a)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceASym0 :: TyFun (t (f a)) (f (t a)) -> Type) (a6989586621680733990 :: t (f a)) = SequenceA a6989586621680733990

type family SequenceASym1 (a6989586621680733990 :: t (f a)) :: f (t a) where ... Source #

Equations

SequenceASym1 (a6989586621680733990 :: t (f a)) = SequenceA a6989586621680733990 

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) (a6989586621680733994 :: a ~> m b) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym0 :: TyFun (a ~> m b) (t a ~> m (t b)) -> Type) (a6989586621680733994 :: a ~> m b) = MapMSym1 a6989586621680733994 :: TyFun (t a) (m (t b)) -> Type

data MapMSym1 (a6989586621680733994 :: 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 a6989586621680733994 :: TyFun (t a) (m (t b)) -> Type) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym1 a6989586621680733994 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680733995 :: t a) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (MapMSym1 a6989586621680733994 :: TyFun (t a) (m (t b)) -> Type) (a6989586621680733995 :: t a) = MapM a6989586621680733994 a6989586621680733995

type family MapMSym2 (a6989586621680733994 :: a ~> m b) (a6989586621680733995 :: t a) :: m (t b) where ... Source #

Equations

MapMSym2 (a6989586621680733994 :: a ~> m b) (a6989586621680733995 :: t a) = MapM a6989586621680733994 a6989586621680733995 

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) (a6989586621680733998 :: t (m a)) Source # 
Instance details

Defined in Data.Traversable.Singletons

type Apply (SequenceSym0 :: TyFun (t (m a)) (m (t a)) -> Type) (a6989586621680733998 :: t (m a)) = Sequence a6989586621680733998

type family SequenceSym1 (a6989586621680733998 :: t (m a)) :: m (t a) where ... Source #

Equations

SequenceSym1 (a6989586621680733998 :: t (m a)) = Sequence a6989586621680733998 

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) (a6989586621679180225 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (IdSym0 :: TyFun a a -> Type) (a6989586621679180225 :: a) = Id a6989586621679180225

type family IdSym1 (a6989586621679180225 :: a) :: a where ... Source #

Equations

IdSym1 (a6989586621679180225 :: a) = Id a6989586621679180225 

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) (a6989586621679180220 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym0 :: TyFun a (b ~> a) -> Type) (a6989586621679180220 :: a) = ConstSym1 a6989586621679180220 :: TyFun b a -> Type

data ConstSym1 (a6989586621679180220 :: 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 a6989586621679180220 :: TyFun b a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym1 a6989586621679180220 :: TyFun b a -> Type) (a6989586621679180221 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (ConstSym1 a6989586621679180220 :: TyFun b a -> Type) (a6989586621679180221 :: b) = Const a6989586621679180220 a6989586621679180221

type family ConstSym2 (a6989586621679180220 :: a) (a6989586621679180221 :: b) :: a where ... Source #

Equations

ConstSym2 (a6989586621679180220 :: a) (a6989586621679180221 :: b) = Const a6989586621679180220 a6989586621679180221 

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) (a6989586621679180207 :: b ~> c) Source # 
Instance details

Defined in GHC.Base.Singletons

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

data (a6989586621679180207 :: 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 ((.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679180208 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((.@#@$$) a6989586621679180207 :: TyFun (a ~> b) (a ~> c) -> Type) (a6989586621679180208 :: a ~> b) = a6989586621679180207 .@#@$$$ a6989586621679180208

data ((a6989586621679180207 :: b ~> c) .@#@$$$ (a6989586621679180208 :: 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 (a6989586621679180207 .@#@$$$ a6989586621679180208 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (a6989586621679180207 .@#@$$$ a6989586621679180208 :: TyFun a c -> Type) (a6989586621679180209 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (a6989586621679180207 .@#@$$$ a6989586621679180208 :: TyFun a c -> Type) (a6989586621679180209 :: a) = (a6989586621679180207 . a6989586621679180208) a6989586621679180209

type family ((a6989586621679180207 :: b ~> c) .@#@$$$$ (a6989586621679180208 :: a ~> b)) (a6989586621679180209 :: a) :: c where ... infixr 9 Source #

Equations

((a6989586621679180207 :: b ~> c) .@#@$$$$ (a6989586621679180208 :: a ~> b)) (a6989586621679180209 :: a) = (a6989586621679180207 . a6989586621679180208) a6989586621679180209 

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) (a6989586621679180195 :: a ~> (b ~> c)) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym0 :: TyFun (a ~> (b ~> c)) (b ~> (a ~> c)) -> Type) (a6989586621679180195 :: a ~> (b ~> c)) = FlipSym1 a6989586621679180195

data FlipSym1 (a6989586621679180195 :: 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 a6989586621679180195 :: TyFun b (a ~> c) -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679180195 :: TyFun b (a ~> c) -> Type) (a6989586621679180196 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym1 a6989586621679180195 :: TyFun b (a ~> c) -> Type) (a6989586621679180196 :: b) = FlipSym2 a6989586621679180195 a6989586621679180196

data FlipSym2 (a6989586621679180195 :: a ~> (b ~> c)) (a6989586621679180196 :: 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 a6989586621679180195 a6989586621679180196 :: TyFun a c -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym2 a6989586621679180195 a6989586621679180196 :: TyFun a c -> Type) (a6989586621679180197 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (FlipSym2 a6989586621679180195 a6989586621679180196 :: TyFun a c -> Type) (a6989586621679180197 :: a) = Flip a6989586621679180195 a6989586621679180196 a6989586621679180197

type family FlipSym3 (a6989586621679180195 :: a ~> (b ~> c)) (a6989586621679180196 :: b) (a6989586621679180197 :: a) :: c where ... Source #

Equations

FlipSym3 (a6989586621679180195 :: a ~> (b ~> c)) (a6989586621679180196 :: b) (a6989586621679180197 :: a) = Flip a6989586621679180195 a6989586621679180196 a6989586621679180197 

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) (a6989586621679180176 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

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

data (a6989586621679180176 :: 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 (($@#@$$) a6989586621679180176 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$$) a6989586621679180176 :: TyFun a b -> Type) (a6989586621679180177 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($@#@$$) a6989586621679180176 :: TyFun a b -> Type) (a6989586621679180177 :: a) = a6989586621679180176 $ a6989586621679180177

type family (a6989586621679180176 :: a ~> b) $@#@$$$ (a6989586621679180177 :: a) :: b where ... infixr 0 Source #

Equations

(a6989586621679180176 :: a ~> b) $@#@$$$ (a6989586621679180177 :: a) = a6989586621679180176 $ a6989586621679180177 

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) (a6989586621679180149 :: a ~> Bool) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym0 :: TyFun (a ~> Bool) ((a ~> a) ~> (a ~> a)) -> Type) (a6989586621679180149 :: a ~> Bool) = UntilSym1 a6989586621679180149

data UntilSym1 (a6989586621679180149 :: 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 a6989586621679180149 :: 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 a6989586621679180149 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679180150 :: a ~> a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym1 a6989586621679180149 :: TyFun (a ~> a) (a ~> a) -> Type) (a6989586621679180150 :: a ~> a) = UntilSym2 a6989586621679180149 a6989586621679180150

data UntilSym2 (a6989586621679180149 :: a ~> Bool) (a6989586621679180150 :: 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 a6989586621679180149 a6989586621679180150 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym2 a6989586621679180149 a6989586621679180150 :: TyFun a a -> Type) (a6989586621679180151 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (UntilSym2 a6989586621679180149 a6989586621679180150 :: TyFun a a -> Type) (a6989586621679180151 :: a) = Until a6989586621679180149 a6989586621679180150 a6989586621679180151

type family UntilSym3 (a6989586621679180149 :: a ~> Bool) (a6989586621679180150 :: a ~> a) (a6989586621679180151 :: a) :: a where ... Source #

Equations

UntilSym3 (a6989586621679180149 :: a ~> Bool) (a6989586621679180150 :: a ~> a) (a6989586621679180151 :: a) = Until a6989586621679180149 a6989586621679180150 a6989586621679180151 

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) (a6989586621679180187 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym0 :: TyFun a (a ~> a) -> Type) (a6989586621679180187 :: a) = AsTypeOfSym1 a6989586621679180187

data AsTypeOfSym1 (a6989586621679180187 :: 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 a6989586621679180187 :: TyFun a a -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym1 a6989586621679180187 :: TyFun a a -> Type) (a6989586621679180188 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (AsTypeOfSym1 a6989586621679180187 :: TyFun a a -> Type) (a6989586621679180188 :: a) = AsTypeOf a6989586621679180187 a6989586621679180188

type family AsTypeOfSym2 (a6989586621679180187 :: a) (a6989586621679180188 :: a) :: a where ... Source #

Equations

AsTypeOfSym2 (a6989586621679180187 :: a) (a6989586621679180188 :: a) = AsTypeOf a6989586621679180187 a6989586621679180188 

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 k2 -> Type) (a6989586621679555664 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555664 :: Symbol) = Error a6989586621679555664 :: k2

type family ErrorSym1 (a6989586621679555664 :: Symbol) :: a where ... Source #

Equations

ErrorSym1 a6989586621679555664 = Error a6989586621679555664 :: 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 k2 -> Type) (a6989586621679555924 :: Symbol) Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Apply (ErrorWithoutStackTraceSym0 :: TyFun Symbol k2 -> Type) (a6989586621679555924 :: Symbol) = ErrorWithoutStackTrace a6989586621679555924 :: k2

type family ErrorWithoutStackTraceSym1 (a6989586621679555924 :: Symbol) :: a where ... Source #

Equations

ErrorWithoutStackTraceSym1 a6989586621679555924 = ErrorWithoutStackTrace a6989586621679555924 :: a 

type family UndefinedSym0 :: a where ... Source #

Equations

UndefinedSym0 = Undefined :: a 

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) (a6989586621679180140 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym0 :: TyFun a (b ~> b) -> Type) (a6989586621679180140 :: a) = SeqSym1 a6989586621679180140 :: TyFun b b -> Type

data SeqSym1 (a6989586621679180140 :: 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 a6989586621679180140 :: TyFun b b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym1 a6989586621679180140 :: TyFun b b -> Type) (a6989586621679180141 :: b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (SeqSym1 a6989586621679180140 :: TyFun b b -> Type) (a6989586621679180141 :: b) = Seq a6989586621679180140 a6989586621679180141

type family SeqSym2 (a6989586621679180140 :: a) (a6989586621679180141 :: b) :: b where ... infixr 0 Source #

Equations

SeqSym2 (a6989586621679180140 :: a) (a6989586621679180141 :: b) = Seq a6989586621679180140 a6989586621679180141 

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) (a6989586621679180167 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

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

data (a6989586621679180167 :: 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 (($!@#@$$) a6989586621679180167 :: TyFun a b -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$$) a6989586621679180167 :: TyFun a b -> Type) (a6989586621679180168 :: a) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (($!@#@$$) a6989586621679180167 :: TyFun a b -> Type) (a6989586621679180168 :: a) = a6989586621679180167 $! a6989586621679180168

type family (a6989586621679180167 :: a ~> b) $!@#@$$$ (a6989586621679180168 :: a) :: b where ... infixr 0 Source #

Equations

(a6989586621679180167 :: a ~> b) $!@#@$$$ (a6989586621679180168 :: a) = a6989586621679180167 $! a6989586621679180168 

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) (a6989586621679180239 :: a ~> b) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym0 :: TyFun (a ~> b) ([a] ~> [b]) -> Type) (a6989586621679180239 :: a ~> b) = MapSym1 a6989586621679180239

data MapSym1 (a6989586621679180239 :: 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 a6989586621679180239 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym1 a6989586621679180239 :: TyFun [a] [b] -> Type) (a6989586621679180240 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply (MapSym1 a6989586621679180239 :: TyFun [a] [b] -> Type) (a6989586621679180240 :: [a]) = Map a6989586621679180239 a6989586621679180240

type family MapSym2 (a6989586621679180239 :: a ~> b) (a6989586621679180240 :: [a]) :: [b] where ... Source #

Equations

MapSym2 (a6989586621679180239 :: a ~> b) (a6989586621679180240 :: [a]) = Map a6989586621679180239 a6989586621679180240 

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) (a6989586621679180230 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$) :: TyFun [a] ([a] ~> [a]) -> Type) (a6989586621679180230 :: [a]) = (++@#@$$) a6989586621679180230

data (a6989586621679180230 :: [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 ((++@#@$$) a6989586621679180230 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$$) a6989586621679180230 :: TyFun [a] [a] -> Type) (a6989586621679180231 :: [a]) Source # 
Instance details

Defined in GHC.Base.Singletons

type Apply ((++@#@$$) a6989586621679180230 :: TyFun [a] [a] -> Type) (a6989586621679180231 :: [a]) = a6989586621679180230 ++ a6989586621679180231

type family (a6989586621679180230 :: [a]) ++@#@$$$ (a6989586621679180231 :: [a]) :: [a] where ... infixr 5 Source #

Equations

(a6989586621679180230 :: [a]) ++@#@$$$ (a6989586621679180231 :: [a]) = a6989586621679180230 ++ a6989586621679180231 

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) (a6989586621679815053 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679815053 :: a ~> Bool) = FilterSym1 a6989586621679815053

data FilterSym1 (a6989586621679815053 :: 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 a6989586621679815053 :: 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 a6989586621679815053 :: TyFun [a] [a] -> Type) (a6989586621679815054 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (FilterSym1 a6989586621679815053 :: TyFun [a] [a] -> Type) (a6989586621679815054 :: [a]) = Filter a6989586621679815053 a6989586621679815054

type family FilterSym2 (a6989586621679815053 :: a ~> Bool) (a6989586621679815054 :: [a]) :: [a] where ... Source #

Equations

FilterSym2 (a6989586621679815053 :: a ~> Bool) (a6989586621679815054 :: [a]) = Filter a6989586621679815053 a6989586621679815054 

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) (a6989586621679815823 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (HeadSym0 :: TyFun [a] a -> Type) (a6989586621679815823 :: [a]) = Head a6989586621679815823

type family HeadSym1 (a6989586621679815823 :: [a]) :: a where ... Source #

Equations

HeadSym1 (a6989586621679815823 :: [a]) = Head a6989586621679815823 

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) (a6989586621679815817 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LastSym0 :: TyFun [a] a -> Type) (a6989586621679815817 :: [a]) = Last a6989586621679815817

type family LastSym1 (a6989586621679815817 :: [a]) :: a where ... Source #

Equations

LastSym1 (a6989586621679815817 :: [a]) = Last a6989586621679815817 

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) (a6989586621679815813 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TailSym0 :: TyFun [a] [a] -> Type) (a6989586621679815813 :: [a]) = Tail a6989586621679815813

type family TailSym1 (a6989586621679815813 :: [a]) :: [a] where ... Source #

Equations

TailSym1 (a6989586621679815813 :: [a]) = Tail a6989586621679815813 

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) (a6989586621679815801 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (InitSym0 :: TyFun [a] [a] -> Type) (a6989586621679815801 :: [a]) = Init a6989586621679815801

type family InitSym1 (a6989586621679815801 :: [a]) :: [a] where ... Source #

Equations

InitSym1 (a6989586621679815801 :: [a]) = Init a6989586621679815801 

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) (a6989586621679814661 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$) :: TyFun [a] (Natural ~> a) -> Type) (a6989586621679814661 :: [a]) = (!!@#@$$) a6989586621679814661

data (a6989586621679814661 :: [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 ((!!@#@$$) a6989586621679814661 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$$) a6989586621679814661 :: TyFun Natural a -> Type) (a6989586621679814662 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply ((!!@#@$$) a6989586621679814661 :: TyFun Natural a -> Type) (a6989586621679814662 :: Natural) = a6989586621679814661 !! a6989586621679814662

type family (a6989586621679814661 :: [a]) !!@#@$$$ (a6989586621679814662 :: Natural) :: a where ... infixl 9 Source #

Equations

(a6989586621679814661 :: [a]) !!@#@$$$ a6989586621679814662 = a6989586621679814661 !! a6989586621679814662 

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) (a6989586621680390432 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680390432 :: t a) = Null a6989586621680390432

type family NullSym1 (a6989586621680390432 :: t a) :: Bool where ... Source #

Equations

NullSym1 (a6989586621680390432 :: t a) = Null a6989586621680390432 

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) (a6989586621680390435 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680390435 :: t a) = Length a6989586621680390435

type family LengthSym1 (a6989586621680390435 :: t a) :: Natural where ... Source #

Equations

LengthSym1 (a6989586621680390435 :: t a) = Length a6989586621680390435 

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) (a6989586621679815786 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReverseSym0 :: TyFun [a] [a] -> Type) (a6989586621679815786 :: [a]) = Reverse a6989586621679815786

type family ReverseSym1 (a6989586621679815786 :: [a]) :: [a] where ... Source #

Equations

ReverseSym1 (a6989586621679815786 :: [a]) = Reverse a6989586621679815786 

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) (a6989586621680390258 :: t Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680390258 :: t Bool) = And a6989586621680390258

type family AndSym1 (a6989586621680390258 :: t Bool) :: Bool where ... Source #

Equations

AndSym1 (a6989586621680390258 :: t Bool) = And a6989586621680390258 

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) (a6989586621680390252 :: t Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680390252 :: t Bool) = Or a6989586621680390252

type family OrSym1 (a6989586621680390252 :: t Bool) :: Bool where ... Source #

Equations

OrSym1 (a6989586621680390252 :: t Bool) = Or a6989586621680390252 

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) (a6989586621680390244 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390244 :: a ~> Bool) = AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type

data AnySym1 (a6989586621680390244 :: 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 a6989586621680390244 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type) (a6989586621680390245 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621680390244 :: TyFun (t a) Bool -> Type) (a6989586621680390245 :: t a) = Any a6989586621680390244 a6989586621680390245

type family AnySym2 (a6989586621680390244 :: a ~> Bool) (a6989586621680390245 :: t a) :: Bool where ... Source #

Equations

AnySym2 (a6989586621680390244 :: a ~> Bool) (a6989586621680390245 :: t a) = Any a6989586621680390244 a6989586621680390245 

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) (a6989586621680390235 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680390235 :: a ~> Bool) = AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type

data AllSym1 (a6989586621680390235 :: 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 a6989586621680390235 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type) (a6989586621680390236 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621680390235 :: TyFun (t a) Bool -> Type) (a6989586621680390236 :: t a) = All a6989586621680390235 a6989586621680390236

type family AllSym2 (a6989586621680390235 :: a ~> Bool) (a6989586621680390236 :: t a) :: Bool where ... Source #

Equations

AllSym2 (a6989586621680390235 :: a ~> Bool) (a6989586621680390236 :: t a) = All a6989586621680390235 a6989586621680390236 

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) (a6989586621680390274 :: t [a]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680390274 :: t [a]) = Concat a6989586621680390274

type family ConcatSym1 (a6989586621680390274 :: t [a]) :: [a] where ... Source #

Equations

ConcatSym1 (a6989586621680390274 :: t [a]) = Concat a6989586621680390274 

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) (a6989586621680390263 :: a ~> [b]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680390263 :: a ~> [b]) = ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type

data ConcatMapSym1 (a6989586621680390263 :: 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 a6989586621680390263 :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type) (a6989586621680390264 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym1 a6989586621680390263 :: TyFun (t a) [b] -> Type) (a6989586621680390264 :: t a) = ConcatMap a6989586621680390263 a6989586621680390264

type family ConcatMapSym2 (a6989586621680390263 :: a ~> [b]) (a6989586621680390264 :: t a) :: [b] where ... Source #

Equations

ConcatMapSym2 (a6989586621680390263 :: a ~> [b]) (a6989586621680390264 :: t a) = ConcatMap a6989586621680390263 a6989586621680390264 

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) (a6989586621679815591 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym0 :: TyFun (b ~> (a ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815591 :: b ~> (a ~> b)) = ScanlSym1 a6989586621679815591

data ScanlSym1 (a6989586621679815591 :: 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 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815592 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym1 a6989586621679815591 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815592 :: b) = ScanlSym2 a6989586621679815591 a6989586621679815592

data ScanlSym2 (a6989586621679815591 :: b ~> (a ~> b)) (a6989586621679815592 :: 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 a6989586621679815591 a6989586621679815592 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym2 a6989586621679815591 a6989586621679815592 :: TyFun [a] [b] -> Type) (a6989586621679815593 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanlSym2 a6989586621679815591 a6989586621679815592 :: TyFun [a] [b] -> Type) (a6989586621679815593 :: [a]) = Scanl a6989586621679815591 a6989586621679815592 a6989586621679815593

type family ScanlSym3 (a6989586621679815591 :: b ~> (a ~> b)) (a6989586621679815592 :: b) (a6989586621679815593 :: [a]) :: [b] where ... Source #

Equations

ScanlSym3 (a6989586621679815591 :: b ~> (a ~> b)) (a6989586621679815592 :: b) (a6989586621679815593 :: [a]) = Scanl a6989586621679815591 a6989586621679815592 a6989586621679815593 

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) (a6989586621679815582 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815582 :: a ~> (a ~> a)) = Scanl1Sym1 a6989586621679815582

data Scanl1Sym1 (a6989586621679815582 :: 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 a6989586621679815582 :: 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 a6989586621679815582 :: TyFun [a] [a] -> Type) (a6989586621679815583 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanl1Sym1 a6989586621679815582 :: TyFun [a] [a] -> Type) (a6989586621679815583 :: [a]) = Scanl1 a6989586621679815582 a6989586621679815583

type family Scanl1Sym2 (a6989586621679815582 :: a ~> (a ~> a)) (a6989586621679815583 :: [a]) :: [a] where ... Source #

Equations

Scanl1Sym2 (a6989586621679815582 :: a ~> (a ~> a)) (a6989586621679815583 :: [a]) = Scanl1 a6989586621679815582 a6989586621679815583 

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) (a6989586621679815564 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym0 :: TyFun (a ~> (b ~> b)) (b ~> ([a] ~> [b])) -> Type) (a6989586621679815564 :: a ~> (b ~> b)) = ScanrSym1 a6989586621679815564

data ScanrSym1 (a6989586621679815564 :: 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 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815565 :: b) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym1 a6989586621679815564 :: TyFun b ([a] ~> [b]) -> Type) (a6989586621679815565 :: b) = ScanrSym2 a6989586621679815564 a6989586621679815565

data ScanrSym2 (a6989586621679815564 :: a ~> (b ~> b)) (a6989586621679815565 :: 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 a6989586621679815564 a6989586621679815565 :: TyFun [a] [b] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym2 a6989586621679815564 a6989586621679815565 :: TyFun [a] [b] -> Type) (a6989586621679815566 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ScanrSym2 a6989586621679815564 a6989586621679815565 :: TyFun [a] [b] -> Type) (a6989586621679815566 :: [a]) = Scanr a6989586621679815564 a6989586621679815565 a6989586621679815566

type family ScanrSym3 (a6989586621679815564 :: a ~> (b ~> b)) (a6989586621679815565 :: b) (a6989586621679815566 :: [a]) :: [b] where ... Source #

Equations

ScanrSym3 (a6989586621679815564 :: a ~> (b ~> b)) (a6989586621679815565 :: b) (a6989586621679815566 :: [a]) = Scanr a6989586621679815564 a6989586621679815565 a6989586621679815566 

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) (a6989586621679815544 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym0 :: TyFun (a ~> (a ~> a)) ([a] ~> [a]) -> Type) (a6989586621679815544 :: a ~> (a ~> a)) = Scanr1Sym1 a6989586621679815544

data Scanr1Sym1 (a6989586621679815544 :: 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 a6989586621679815544 :: 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 a6989586621679815544 :: TyFun [a] [a] -> Type) (a6989586621679815545 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Scanr1Sym1 a6989586621679815544 :: TyFun [a] [a] -> Type) (a6989586621679815545 :: [a]) = Scanr1 a6989586621679815544 a6989586621679815545

type family Scanr1Sym2 (a6989586621679815544 :: a ~> (a ~> a)) (a6989586621679815545 :: [a]) :: [a] where ... Source #

Equations

Scanr1Sym2 (a6989586621679815544 :: a ~> (a ~> a)) (a6989586621679815545 :: [a]) = Scanr1 a6989586621679815544 a6989586621679815545 

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) (a6989586621679814681 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym0 :: TyFun Natural (a ~> [a]) -> Type) (a6989586621679814681 :: Natural) = ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type

data ReplicateSym1 (a6989586621679814681 :: 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 a6989586621679814681 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type) (a6989586621679814682 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ReplicateSym1 a6989586621679814681 :: TyFun a [a] -> Type) (a6989586621679814682 :: a) = Replicate a6989586621679814681 a6989586621679814682

type family ReplicateSym2 (a6989586621679814681 :: Natural) (a6989586621679814682 :: a) :: [a] where ... Source #

Equations

ReplicateSym2 a6989586621679814681 (a6989586621679814682 :: a) = Replicate a6989586621679814681 a6989586621679814682 

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) (a6989586621679814836 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679814836 :: Natural) = TakeSym1 a6989586621679814836 :: TyFun [a] [a] -> Type

data TakeSym1 (a6989586621679814836 :: 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 a6989586621679814836 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym1 a6989586621679814836 :: TyFun [a] [a] -> Type) (a6989586621679814837 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeSym1 a6989586621679814836 :: TyFun [a] [a] -> Type) (a6989586621679814837 :: [a]) = Take a6989586621679814836 a6989586621679814837

type family TakeSym2 (a6989586621679814836 :: Natural) (a6989586621679814837 :: [a]) :: [a] where ... Source #

Equations

TakeSym2 a6989586621679814836 (a6989586621679814837 :: [a]) = Take a6989586621679814836 a6989586621679814837 

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) (a6989586621679814823 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym0 :: TyFun Natural ([a] ~> [a]) -> Type) (a6989586621679814823 :: Natural) = DropSym1 a6989586621679814823 :: TyFun [a] [a] -> Type

data DropSym1 (a6989586621679814823 :: 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 a6989586621679814823 :: TyFun [a] [a] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym1 a6989586621679814823 :: TyFun [a] [a] -> Type) (a6989586621679814824 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropSym1 a6989586621679814823 :: TyFun [a] [a] -> Type) (a6989586621679814824 :: [a]) = Drop a6989586621679814823 a6989586621679814824

type family DropSym2 (a6989586621679814823 :: Natural) (a6989586621679814824 :: [a]) :: [a] where ... Source #

Equations

DropSym2 a6989586621679814823 (a6989586621679814824 :: [a]) = Drop a6989586621679814823 a6989586621679814824 

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) (a6989586621679814953 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814953 :: a ~> Bool) = TakeWhileSym1 a6989586621679814953

data TakeWhileSym1 (a6989586621679814953 :: 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 a6989586621679814953 :: 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 a6989586621679814953 :: TyFun [a] [a] -> Type) (a6989586621679814954 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (TakeWhileSym1 a6989586621679814953 :: TyFun [a] [a] -> Type) (a6989586621679814954 :: [a]) = TakeWhile a6989586621679814953 a6989586621679814954

type family TakeWhileSym2 (a6989586621679814953 :: a ~> Bool) (a6989586621679814954 :: [a]) :: [a] where ... Source #

Equations

TakeWhileSym2 (a6989586621679814953 :: a ~> Bool) (a6989586621679814954 :: [a]) = TakeWhile a6989586621679814953 a6989586621679814954 

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) (a6989586621679814938 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814938 :: a ~> Bool) = DropWhileSym1 a6989586621679814938

data DropWhileSym1 (a6989586621679814938 :: 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 a6989586621679814938 :: 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 a6989586621679814938 :: TyFun [a] [a] -> Type) (a6989586621679814939 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileSym1 a6989586621679814938 :: TyFun [a] [a] -> Type) (a6989586621679814939 :: [a]) = DropWhile a6989586621679814938 a6989586621679814939

type family DropWhileSym2 (a6989586621679814938 :: a ~> Bool) (a6989586621679814939 :: [a]) :: [a] where ... Source #

Equations

DropWhileSym2 (a6989586621679814938 :: a ~> Bool) (a6989586621679814939 :: [a]) = DropWhile a6989586621679814938 a6989586621679814939 

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) (a6989586621679814921 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym0 :: TyFun (a ~> Bool) ([a] ~> [a]) -> Type) (a6989586621679814921 :: a ~> Bool) = DropWhileEndSym1 a6989586621679814921

data DropWhileEndSym1 (a6989586621679814921 :: 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 a6989586621679814921 :: 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 a6989586621679814921 :: TyFun [a] [a] -> Type) (a6989586621679814922 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (DropWhileEndSym1 a6989586621679814921 :: TyFun [a] [a] -> Type) (a6989586621679814922 :: [a]) = DropWhileEnd a6989586621679814921 a6989586621679814922

type family DropWhileEndSym2 (a6989586621679814921 :: a ~> Bool) (a6989586621679814922 :: [a]) :: [a] where ... Source #

Equations

DropWhileEndSym2 (a6989586621679814921 :: a ~> Bool) (a6989586621679814922 :: [a]) = DropWhileEnd a6989586621679814921 a6989586621679814922 

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) (a6989586621679814884 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814884 :: a ~> Bool) = SpanSym1 a6989586621679814884

data SpanSym1 (a6989586621679814884 :: 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 a6989586621679814884 :: 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 a6989586621679814884 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814885 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SpanSym1 a6989586621679814884 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814885 :: [a]) = Span a6989586621679814884 a6989586621679814885

type family SpanSym2 (a6989586621679814884 :: a ~> Bool) (a6989586621679814885 :: [a]) :: ([a], [a]) where ... Source #

Equations

SpanSym2 (a6989586621679814884 :: a ~> Bool) (a6989586621679814885 :: [a]) = Span a6989586621679814884 a6989586621679814885 

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) (a6989586621679814849 :: a ~> Bool) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym0 :: TyFun (a ~> Bool) ([a] ~> ([a], [a])) -> Type) (a6989586621679814849 :: a ~> Bool) = BreakSym1 a6989586621679814849

data BreakSym1 (a6989586621679814849 :: 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 a6989586621679814849 :: 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 a6989586621679814849 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814850 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (BreakSym1 a6989586621679814849 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814850 :: [a]) = Break a6989586621679814849 a6989586621679814850

type family BreakSym2 (a6989586621679814849 :: a ~> Bool) (a6989586621679814850 :: [a]) :: ([a], [a]) where ... Source #

Equations

BreakSym2 (a6989586621679814849 :: a ~> Bool) (a6989586621679814850 :: [a]) = Break a6989586621679814849 a6989586621679814850 

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) (a6989586621679814816 :: Natural) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym0 :: TyFun Natural ([a] ~> ([a], [a])) -> Type) (a6989586621679814816 :: Natural) = SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type

data SplitAtSym1 (a6989586621679814816 :: 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 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814817 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (SplitAtSym1 a6989586621679814816 :: TyFun [a] ([a], [a]) -> Type) (a6989586621679814817 :: [a]) = SplitAt a6989586621679814816 a6989586621679814817

type family SplitAtSym2 (a6989586621679814816 :: Natural) (a6989586621679814817 :: [a]) :: ([a], [a]) where ... Source #

Equations

SplitAtSym2 a6989586621679814816 (a6989586621679814817 :: [a]) = SplitAt a6989586621679814816 a6989586621679814817 

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) (a6989586621680390186 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680390186 :: a) = NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type

data NotElemSym1 (a6989586621680390186 :: 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 a6989586621680390186 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type) (a6989586621680390187 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621680390186 :: TyFun (t a) Bool -> Type) (a6989586621680390187 :: t a) = NotElem a6989586621680390186 a6989586621680390187

type family NotElemSym2 (a6989586621680390186 :: a) (a6989586621680390187 :: t a) :: Bool where ... Source #

Equations

NotElemSym2 (a6989586621680390186 :: a) (a6989586621680390187 :: t a) = NotElem a6989586621680390186 a6989586621680390187 

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) (a6989586621679814744 :: a) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym0 :: TyFun a ([(a, b)] ~> Maybe b) -> Type) (a6989586621679814744 :: a) = LookupSym1 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type

data LookupSym1 (a6989586621679814744 :: 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 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym1 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679814745 :: [(a, b)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (LookupSym1 a6989586621679814744 :: TyFun [(a, b)] (Maybe b) -> Type) (a6989586621679814745 :: [(a, b)]) = Lookup a6989586621679814744 a6989586621679814745

type family LookupSym2 (a6989586621679814744 :: a) (a6989586621679814745 :: [(a, b)]) :: Maybe b where ... Source #

Equations

LookupSym2 (a6989586621679814744 :: a) (a6989586621679814745 :: [(a, b)]) = Lookup a6989586621679814744 a6989586621679814745 

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) (a6989586621679815371 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym0 :: TyFun [a] ([b] ~> [(a, b)]) -> Type) (a6989586621679815371 :: [a]) = ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type

data ZipSym1 (a6989586621679815371 :: [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 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type) (a6989586621679815372 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipSym1 a6989586621679815371 :: TyFun [b] [(a, b)] -> Type) (a6989586621679815372 :: [b]) = Zip a6989586621679815371 a6989586621679815372

type family ZipSym2 (a6989586621679815371 :: [a]) (a6989586621679815372 :: [b]) :: [(a, b)] where ... Source #

Equations

ZipSym2 (a6989586621679815371 :: [a]) (a6989586621679815372 :: [b]) = Zip a6989586621679815371 a6989586621679815372 

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) (a6989586621679815359 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym0 :: TyFun [a] ([b] ~> ([c] ~> [(a, b, c)])) -> Type) (a6989586621679815359 :: [a]) = Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type

data Zip3Sym1 (a6989586621679815359 :: [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 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679815360 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym1 a6989586621679815359 :: TyFun [b] ([c] ~> [(a, b, c)]) -> Type) (a6989586621679815360 :: [b]) = Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type

data Zip3Sym2 (a6989586621679815359 :: [a]) (a6989586621679815360 :: [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 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679815361 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Zip3Sym2 a6989586621679815359 a6989586621679815360 :: TyFun [c] [(a, b, c)] -> Type) (a6989586621679815361 :: [c]) = Zip3 a6989586621679815359 a6989586621679815360 a6989586621679815361

type family Zip3Sym3 (a6989586621679815359 :: [a]) (a6989586621679815360 :: [b]) (a6989586621679815361 :: [c]) :: [(a, b, c)] where ... Source #

Equations

Zip3Sym3 (a6989586621679815359 :: [a]) (a6989586621679815360 :: [b]) (a6989586621679815361 :: [c]) = Zip3 a6989586621679815359 a6989586621679815360 a6989586621679815361 

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) (a6989586621679815347 :: a ~> (b ~> c)) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym0 :: TyFun (a ~> (b ~> c)) ([a] ~> ([b] ~> [c])) -> Type) (a6989586621679815347 :: a ~> (b ~> c)) = ZipWithSym1 a6989586621679815347

data ZipWithSym1 (a6989586621679815347 :: 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 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679815348 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym1 a6989586621679815347 :: TyFun [a] ([b] ~> [c]) -> Type) (a6989586621679815348 :: [a]) = ZipWithSym2 a6989586621679815347 a6989586621679815348

data ZipWithSym2 (a6989586621679815347 :: a ~> (b ~> c)) (a6989586621679815348 :: [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 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym2 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) (a6989586621679815349 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWithSym2 a6989586621679815347 a6989586621679815348 :: TyFun [b] [c] -> Type) (a6989586621679815349 :: [b]) = ZipWith a6989586621679815347 a6989586621679815348 a6989586621679815349

type family ZipWithSym3 (a6989586621679815347 :: a ~> (b ~> c)) (a6989586621679815348 :: [a]) (a6989586621679815349 :: [b]) :: [c] where ... Source #

Equations

ZipWithSym3 (a6989586621679815347 :: a ~> (b ~> c)) (a6989586621679815348 :: [a]) (a6989586621679815349 :: [b]) = ZipWith a6989586621679815347 a6989586621679815348 a6989586621679815349 

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) (a6989586621679815332 :: 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) (a6989586621679815332 :: a ~> (b ~> (c ~> d))) = ZipWith3Sym1 a6989586621679815332

data ZipWith3Sym1 (a6989586621679815332 :: 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 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679815333 :: [a]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym1 a6989586621679815332 :: TyFun [a] ([b] ~> ([c] ~> [d])) -> Type) (a6989586621679815333 :: [a]) = ZipWith3Sym2 a6989586621679815332 a6989586621679815333

data ZipWith3Sym2 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [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 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679815334 :: [b]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym2 a6989586621679815332 a6989586621679815333 :: TyFun [b] ([c] ~> [d]) -> Type) (a6989586621679815334 :: [b]) = ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334

data ZipWith3Sym3 (a6989586621679815332 :: a ~> (b ~> (c ~> d))) (a6989586621679815333 :: [a]) (a6989586621679815334 :: [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 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) (a6989586621679815335 :: [c]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (ZipWith3Sym3 a6989586621679815332 a6989586621679815333 a6989586621679815334 :: TyFun [c] [d] -> Type) (a6989586621679815335 :: [c]) = ZipWith3 a6989586621679815332 a6989586621679815333 a6989586621679815334 a6989586621679815335

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) (a6989586621679815313 :: [(a, b)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (UnzipSym0 :: TyFun [(a, b)] ([a], [b]) -> Type) (a6989586621679815313 :: [(a, b)]) = Unzip a6989586621679815313

type family UnzipSym1 (a6989586621679815313 :: [(a, b)]) :: ([a], [b]) where ... Source #

Equations

UnzipSym1 (a6989586621679815313 :: [(a, b)]) = Unzip a6989586621679815313 

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) (a6989586621679815295 :: [(a, b, c)]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply (Unzip3Sym0 :: TyFun [(a, b, c)] ([a], [b], [c]) -> Type) (a6989586621679815295 :: [(a, b, c)]) = Unzip3 a6989586621679815295

type family Unzip3Sym1 (a6989586621679815295 :: [(a, b, c)]) :: ([a], [b], [c]) where ... Source #

Equations

Unzip3Sym1 (a6989586621679815295 :: [(a, b, c)]) = Unzip3 a6989586621679815295 

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 (a6989586621679815198 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnlinesSym0 (a6989586621679815198 :: [Symbol]) = Unlines a6989586621679815198

type family UnlinesSym1 (a6989586621679815198 :: [Symbol]) :: Symbol where ... Source #

Equations

UnlinesSym1 a6989586621679815198 = Unlines a6989586621679815198 

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 (a6989586621679815188 :: [Symbol]) Source # 
Instance details

Defined in Data.List.Singletons.Internal

type Apply UnwordsSym0 (a6989586621679815188 :: [Symbol]) = Unwords a6989586621679815188

type family UnwordsSym1 (a6989586621679815188 :: [Symbol]) :: Symbol where ... Source #

Equations

UnwordsSym1 a6989586621679815188 = Unwords a6989586621679815188 

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) (a6989586621680208714 :: Natural) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208714 :: Natural) = ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type

data ShowsPrecSym1 (a6989586621680208714 :: 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 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) = ShowsPrecSym2 a6989586621680208714 a6989586621680208715

data ShowsPrecSym2 (a6989586621680208714 :: Natural) (a6989586621680208715 :: 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 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) (a6989586621680208716 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) (a6989586621680208716 :: Symbol) = ShowsPrec a6989586621680208714 a6989586621680208715 a6989586621680208716

type family ShowsPrecSym3 (a6989586621680208714 :: Natural) (a6989586621680208715 :: a) (a6989586621680208716 :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrecSym3 a6989586621680208714 (a6989586621680208715 :: a) a6989586621680208716 = ShowsPrec a6989586621680208714 a6989586621680208715 a6989586621680208716 

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) (a6989586621680208723 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208723 :: [a]) = ShowListSym1 a6989586621680208723

data ShowListSym1 (a6989586621680208723 :: [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 a6989586621680208723 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) (a6989586621680208724 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) (a6989586621680208724 :: Symbol) = ShowList a6989586621680208723 a6989586621680208724

type family ShowListSym2 (a6989586621680208723 :: [a]) (a6989586621680208724 :: Symbol) :: Symbol where ... Source #

Equations

ShowListSym2 (a6989586621680208723 :: [a]) a6989586621680208724 = ShowList a6989586621680208723 a6989586621680208724 

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) (a6989586621680208719 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (a6989586621680208719 :: a) = Show_ a6989586621680208719

type family Show_Sym1 (a6989586621680208719 :: a) :: Symbol where ... Source #

Equations

Show_Sym1 (a6989586621680208719 :: a) = Show_ a6989586621680208719 

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) (a6989586621680208706 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208706 :: a) = ShowsSym1 a6989586621680208706

data ShowsSym1 (a6989586621680208706 :: 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 a6989586621680208706 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) (a6989586621680208707 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) (a6989586621680208707 :: Symbol) = Shows a6989586621680208706 a6989586621680208707

type family ShowsSym2 (a6989586621680208706 :: a) (a6989586621680208707 :: Symbol) :: Symbol where ... Source #

Equations

ShowsSym2 (a6989586621680208706 :: a) a6989586621680208707 = Shows a6989586621680208706 a6989586621680208707 

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 (a6989586621680208680 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621680208680 :: Char) = ShowCharSym1 a6989586621680208680

data ShowCharSym1 (a6989586621680208680 :: 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 a6989586621680208680 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) (a6989586621680208681 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) (a6989586621680208681 :: Symbol) = ShowChar a6989586621680208680 a6989586621680208681

type family ShowCharSym2 (a6989586621680208680 :: Char) (a6989586621680208681 :: Symbol) :: Symbol where ... Source #

Equations

ShowCharSym2 a6989586621680208680 a6989586621680208681 = ShowChar a6989586621680208680 a6989586621680208681 

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 (a6989586621680208669 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowStringSym0 (a6989586621680208669 :: Symbol) = ShowStringSym1 a6989586621680208669

data ShowStringSym1 (a6989586621680208669 :: 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 a6989586621680208669 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621680208669 :: TyFun Symbol Symbol -> Type) (a6989586621680208670 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621680208669 :: TyFun Symbol Symbol -> Type) (a6989586621680208670 :: Symbol) = ShowString a6989586621680208669 a6989586621680208670

type family ShowStringSym2 (a6989586621680208669 :: Symbol) (a6989586621680208670 :: Symbol) :: Symbol where ... Source #

Equations

ShowStringSym2 a6989586621680208669 a6989586621680208670 = ShowString a6989586621680208669 a6989586621680208670 

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 (a6989586621680208653 :: Bool) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowParenSym0 (a6989586621680208653 :: Bool) = ShowParenSym1 a6989586621680208653

data ShowParenSym1 (a6989586621680208653 :: 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 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621680208653 a6989586621680208654

data ShowParenSym2 (a6989586621680208653 :: Bool) (a6989586621680208654 :: 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 a6989586621680208653 a6989586621680208654 :: 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 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) (a6989586621680208655 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) (a6989586621680208655 :: Symbol) = ShowParen a6989586621680208653 a6989586621680208654 a6989586621680208655