singletons-base-3.1.1: A promoted and singled version of the base library
Copyright(C) 2018 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Foldable.Singletons

Description

Defines the promoted and singled versions of the Foldable type class.

Synopsis

Documentation

class PFoldable t Source #

Associated Types

type Fold (arg :: t m) :: m Source #

type Fold a = Apply Fold_6989586621680438383Sym0 a

type FoldMap (arg :: (~>) a m) (arg :: t a) :: m Source #

type FoldMap a a = Apply (Apply FoldMap_6989586621680438393Sym0 a) a

type Foldr (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b Source #

type Foldr a a a = Apply (Apply (Apply Foldr_6989586621680438407Sym0 a) a) a

type Foldr' (arg :: (~>) a ((~>) b b)) (arg :: b) (arg :: t a) :: b Source #

type Foldr' a a a = Apply (Apply (Apply Foldr'_6989586621680438422Sym0 a) a) a

type Foldl (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #

type Foldl a a a = Apply (Apply (Apply Foldl_6989586621680438445Sym0 a) a) a

type Foldl' (arg :: (~>) b ((~>) a b)) (arg :: b) (arg :: t a) :: b Source #

type Foldl' a a a = Apply (Apply (Apply Foldl'_6989586621680438460Sym0 a) a) a

type Foldr1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #

type Foldr1 a a = Apply (Apply Foldr1_6989586621680438482Sym0 a) a

type Foldl1 (arg :: (~>) a ((~>) a a)) (arg :: t a) :: a Source #

type Foldl1 a a = Apply (Apply Foldl1_6989586621680438503Sym0 a) a

type ToList (arg :: t a) :: [a] Source #

type ToList a = Apply ToList_6989586621680438523Sym0 a

type Null (arg :: t a) :: Bool Source #

type Null a = Apply Null_6989586621680438532Sym0 a

type Length (arg :: t a) :: Natural Source #

type Length a = Apply Length_6989586621680438549Sym0 a

type Elem (arg :: a) (arg :: t a) :: Bool Source #

type Elem a a = Apply (Apply Elem_6989586621680438568Sym0 a) a

type Maximum (arg :: t a) :: a Source #

type Maximum a = Apply Maximum_6989586621680438582Sym0 a

type Minimum (arg :: t a) :: a Source #

type Minimum a = Apply Minimum_6989586621680438597Sym0 a

type Sum (arg :: t a) :: a Source #

type Sum a = Apply Sum_6989586621680438612Sym0 a

type Product (arg :: t a) :: a Source #

type Product a = Apply Product_6989586621680438621Sym0 a

Instances

Instances details
PFoldable Identity Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable First Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Last Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable First Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Last Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Max Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Min Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Dual Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Product Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Sum Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable NonEmpty Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Maybe Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable [] Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Either a) Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

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

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Arg a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable ((,) a) Source # 
Instance details

Defined in Data.Foldable.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Const m :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Product f g) Source # 
Instance details

Defined in Data.Functor.Product.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Sum f g) Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable (Compose f g) Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

class SFoldable t where Source #

Minimal complete definition

Nothing

Methods

sFold :: forall m (t :: t m). SMonoid m => Sing t -> Sing (Apply FoldSym0 t :: m) Source #

default sFold :: forall m (t :: t m). ((Apply FoldSym0 t :: m) ~ Apply Fold_6989586621680438383Sym0 t, SMonoid m) => Sing t -> Sing (Apply FoldSym0 t :: m) Source #

sFoldMap :: forall a m (t :: (~>) a m) (t :: t a). SMonoid m => Sing t -> Sing t -> Sing (Apply (Apply FoldMapSym0 t) t :: m) Source #

default sFoldMap :: forall a m (t :: (~>) a m) (t :: t a). ((Apply (Apply FoldMapSym0 t) t :: m) ~ Apply (Apply FoldMap_6989586621680438393Sym0 t) t, SMonoid m) => Sing t -> Sing t -> Sing (Apply (Apply FoldMapSym0 t) t :: m) Source #

sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #

default sFoldr :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). (Apply (Apply (Apply FoldrSym0 t) t) t :: b) ~ Apply (Apply (Apply Foldr_6989586621680438407Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrSym0 t) t) t :: b) Source #

sFoldr' :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldr'Sym0 t) t) t :: b) Source #

default sFoldr' :: forall a b (t :: (~>) a ((~>) b b)) (t :: b) (t :: t a). (Apply (Apply (Apply Foldr'Sym0 t) t) t :: b) ~ Apply (Apply (Apply Foldr'_6989586621680438422Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldr'Sym0 t) t) t :: b) Source #

sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #

default sFoldl :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). (Apply (Apply (Apply FoldlSym0 t) t) t :: b) ~ Apply (Apply (Apply Foldl_6989586621680438445Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlSym0 t) t) t :: b) Source #

sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #

default sFoldl' :: forall b a (t :: (~>) b ((~>) a b)) (t :: b) (t :: t a). (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) ~ Apply (Apply (Apply Foldl'_6989586621680438460Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Foldl'Sym0 t) t) t :: b) Source #

sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #

default sFoldr1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). (Apply (Apply Foldr1Sym0 t) t :: a) ~ Apply (Apply Foldr1_6989586621680438482Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply Foldr1Sym0 t) t :: a) Source #

sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #

default sFoldl1 :: forall a (t :: (~>) a ((~>) a a)) (t :: t a). (Apply (Apply Foldl1Sym0 t) t :: a) ~ Apply (Apply Foldl1_6989586621680438503Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply Foldl1Sym0 t) t :: a) Source #

sToList :: forall a (t :: t a). Sing t -> Sing (Apply ToListSym0 t :: [a]) Source #

default sToList :: forall a (t :: t a). (Apply ToListSym0 t :: [a]) ~ Apply ToList_6989586621680438523Sym0 t => Sing t -> Sing (Apply ToListSym0 t :: [a]) Source #

sNull :: forall a (t :: t a). Sing t -> Sing (Apply NullSym0 t :: Bool) Source #

default sNull :: forall a (t :: t a). (Apply NullSym0 t :: Bool) ~ Apply Null_6989586621680438532Sym0 t => Sing t -> Sing (Apply NullSym0 t :: Bool) Source #

sLength :: forall a (t :: t a). Sing t -> Sing (Apply LengthSym0 t :: Natural) Source #

default sLength :: forall a (t :: t a). (Apply LengthSym0 t :: Natural) ~ Apply Length_6989586621680438549Sym0 t => Sing t -> Sing (Apply LengthSym0 t :: Natural) Source #

sElem :: forall a (t :: a) (t :: t a). SEq a => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #

default sElem :: forall a (t :: a) (t :: t a). ((Apply (Apply ElemSym0 t) t :: Bool) ~ Apply (Apply Elem_6989586621680438568Sym0 t) t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply ElemSym0 t) t :: Bool) Source #

sMaximum :: forall a (t :: t a). SOrd a => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #

default sMaximum :: forall a (t :: t a). ((Apply MaximumSym0 t :: a) ~ Apply Maximum_6989586621680438582Sym0 t, SOrd a) => Sing t -> Sing (Apply MaximumSym0 t :: a) Source #

sMinimum :: forall a (t :: t a). SOrd a => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #

default sMinimum :: forall a (t :: t a). ((Apply MinimumSym0 t :: a) ~ Apply Minimum_6989586621680438597Sym0 t, SOrd a) => Sing t -> Sing (Apply MinimumSym0 t :: a) Source #

sSum :: forall a (t :: t a). SNum a => Sing t -> Sing (Apply SumSym0 t :: a) Source #

default sSum :: forall a (t :: t a). ((Apply SumSym0 t :: a) ~ Apply Sum_6989586621680438612Sym0 t, SNum a) => Sing t -> Sing (Apply SumSym0 t :: a) Source #

sProduct :: forall a (t :: t a). SNum a => Sing t -> Sing (Apply ProductSym0 t :: a) Source #

default sProduct :: forall a (t :: t a). ((Apply ProductSym0 t :: a) ~ Apply Product_6989586621680438621Sym0 t, SNum a) => Sing t -> Sing (Apply ProductSym0 t :: a) 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Identity a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Identity a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Identity a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Identity a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Identity a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Identity a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: First a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: First a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: First a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: First a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: First a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Last a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Last a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: First a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: First a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: First a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: First a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: First a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: First a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Last a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Last a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Last a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Last a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Max a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Max a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Max a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Max a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Max a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Max a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Min a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Min a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Min a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Min a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Min a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Min a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Dual a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Dual a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Dual a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Dual a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Dual a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Dual a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Product a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Product a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Product a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Product a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Product a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Product a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Sum a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Sum a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Sum a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Sum a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Sum a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Sum a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: NonEmpty a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: NonEmpty a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: NonEmpty a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: NonEmpty a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Maybe a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

sToList :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Maybe a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Maybe a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

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

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

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

sProduct :: forall a (t1 :: Maybe a). SNum a => Sing t1 -> Sing (Apply ProductSym0 t1) Source #

SFoldable [] Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sFold :: forall m (t1 :: [m]). SMonoid m => Sing t1 -> Sing (Apply FoldSym0 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: [a]). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: [a]). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) Source #

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

sNull :: forall a (t1 :: [a]). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: [a]). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: [a]). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

sMaximum :: forall a (t1 :: [a]). SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) Source #

sMinimum :: forall a (t1 :: [a]). SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) Source #

sSum :: forall a (t1 :: [a]). SNum a => Sing t1 -> Sing (Apply SumSym0 t1) Source #

sProduct :: forall a (t1 :: [a]). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: Either a a0). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Either a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Either a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) Source #

sToList :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a0 (t1 :: Either a a0). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: Either a a0). SEq a0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

sMaximum :: forall a0 (t1 :: Either a a0). SOrd a0 => Sing t1 -> Sing (Apply MaximumSym0 t1) Source #

sMinimum :: forall a0 (t1 :: Either a a0). SOrd a0 => Sing t1 -> Sing (Apply MinimumSym0 t1) Source #

sSum :: forall a0 (t1 :: Either a a0). SNum a0 => Sing t1 -> Sing (Apply SumSym0 t1) Source #

sProduct :: forall a0 (t1 :: Either a a0). SNum a0 => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Proxy a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

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

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

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

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

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

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

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

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

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

sProduct :: forall a (t1 :: Proxy a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: Arg a a0). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) Source #

sToList :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a0 (t1 :: Arg a a0). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: Arg a a0). SEq a0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

sMaximum :: forall a0 (t1 :: Arg a a0). SOrd a0 => Sing t1 -> Sing (Apply MaximumSym0 t1) Source #

sMinimum :: forall a0 (t1 :: Arg a a0). SOrd a0 => Sing t1 -> Sing (Apply MinimumSym0 t1) Source #

sSum :: forall a0 (t1 :: Arg a a0). SNum a0 => Sing t1 -> Sing (Apply SumSym0 t1) Source #

sProduct :: forall a0 (t1 :: Arg a a0). SNum a0 => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a0 m (t1 :: a0 ~> m) (t2 :: (a, a0)). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

sFoldr1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) Source #

sFoldl1 :: forall a0 (t1 :: a0 ~> (a0 ~> a0)) (t2 :: (a, a0)). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) Source #

sToList :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a0 (t1 :: (a, a0)). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a0 (t1 :: a0) (t2 :: (a, a0)). SEq a0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

sMaximum :: forall a0 (t1 :: (a, a0)). SOrd a0 => Sing t1 -> Sing (Apply MaximumSym0 t1) Source #

sMinimum :: forall a0 (t1 :: (a, a0)). SOrd a0 => Sing t1 -> Sing (Apply MinimumSym0 t1) Source #

sSum :: forall a0 (t1 :: (a, a0)). SNum a0 => Sing t1 -> Sing (Apply SumSym0 t1) Source #

sProduct :: forall a0 (t1 :: (a, a0)). SNum a0 => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m0 (t1 :: a ~> m0) (t2 :: Const m a). SMonoid m0 => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Const m a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) Source #

sToList :: forall a (t1 :: Const m a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Const m a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Const m a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Const m a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

sMaximum :: forall a (t1 :: Const m a). SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) Source #

sMinimum :: forall a (t1 :: Const m a). SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) Source #

sSum :: forall a (t1 :: Const m a). SNum a => Sing t1 -> Sing (Apply SumSym0 t1) Source #

sProduct :: forall a (t1 :: Const m a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Product f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Product f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) Source #

sToList :: forall a (t1 :: Product f g a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Product f g a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Product f g a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Product f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

sMaximum :: forall a (t1 :: Product f g a). SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) Source #

sMinimum :: forall a (t1 :: Product f g a). SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) Source #

sSum :: forall a (t1 :: Product f g a). SNum a => Sing t1 -> Sing (Apply SumSym0 t1) Source #

sProduct :: forall a (t1 :: Product f g a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Sum f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Sum f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) Source #

sToList :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Sum f g a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Sum f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

sMaximum :: forall a (t1 :: Sum f g a). SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) Source #

sMinimum :: forall a (t1 :: Sum f g a). SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) Source #

sSum :: forall a (t1 :: Sum f g a). SNum a => Sing t1 -> Sing (Apply SumSym0 t1) Source #

sProduct :: forall a (t1 :: Sum f g a). SNum a => Sing t1 -> Sing (Apply ProductSym0 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 t1) Source #

sFoldMap :: forall a m (t1 :: a ~> m) (t2 :: Compose f g a). SMonoid m => Sing t1 -> Sing t2 -> Sing (Apply (Apply FoldMapSym0 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 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 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 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 t1) t2) t3) Source #

sFoldr1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldr1Sym0 t1) t2) Source #

sFoldl1 :: forall a (t1 :: a ~> (a ~> a)) (t2 :: Compose f g a). Sing t1 -> Sing t2 -> Sing (Apply (Apply Foldl1Sym0 t1) t2) Source #

sToList :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (Apply ToListSym0 t1) Source #

sNull :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (Apply NullSym0 t1) Source #

sLength :: forall a (t1 :: Compose f g a). Sing t1 -> Sing (Apply LengthSym0 t1) Source #

sElem :: forall a (t1 :: a) (t2 :: Compose f g a). SEq a => Sing t1 -> Sing t2 -> Sing (Apply (Apply ElemSym0 t1) t2) Source #

sMaximum :: forall a (t1 :: Compose f g a). SOrd a => Sing t1 -> Sing (Apply MaximumSym0 t1) Source #

sMinimum :: forall a (t1 :: Compose f g a). SOrd a => Sing t1 -> Sing (Apply MinimumSym0 t1) Source #

sSum :: forall a (t1 :: Compose f g a). SNum a => Sing t1 -> Sing (Apply SumSym0 t1) Source #

sProduct :: forall a (t1 :: Compose f g a). SNum a => Sing t1 -> Sing (Apply ProductSym0 t1) Source #

type family FoldrM (a :: (~>) a ((~>) b (m b))) (a :: b) (a :: t a) :: m b where ... Source #

Equations

FoldrM f z0 xs = Apply (Apply (Apply (Apply FoldlSym0 (Let6989586621680438302F'Sym3 f z0 xs)) ReturnSym0) xs) z0 

sFoldrM :: forall a b m t (t :: (~>) a ((~>) b (m b))) (t :: b) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldrMSym0 t) t) t :: m b) Source #

type family FoldlM (a :: (~>) b ((~>) a (m b))) (a :: b) (a :: t a) :: m b where ... Source #

Equations

FoldlM f z0 xs = Apply (Apply (Apply (Apply FoldrSym0 (Let6989586621680438284F'Sym3 f z0 xs)) ReturnSym0) xs) z0 

sFoldlM :: forall b a m t (t :: (~>) b ((~>) a (m b))) (t :: b) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply FoldlMSym0 t) t) t :: m b) Source #

type family Traverse_ (a :: (~>) a (f b)) (a :: t a) :: f () where ... Source #

Equations

Traverse_ f a_6989586621680438265 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (.@#@$) (*>@#@$)) f)) (Apply PureSym0 Tuple0Sym0)) a_6989586621680438265 

sTraverse_ :: forall a f b t (t :: (~>) a (f b)) (t :: t a). (SFoldable t, SApplicative f) => Sing t -> Sing t -> Sing (Apply (Apply Traverse_Sym0 t) t :: f ()) Source #

type family For_ (a :: t a) (a :: (~>) a (f b)) :: f () where ... Source #

Equations

For_ a_6989586621680438254 a_6989586621680438256 = Apply (Apply (Apply FlipSym0 Traverse_Sym0) a_6989586621680438254) a_6989586621680438256 

sFor_ :: forall t a f b (t :: t a) (t :: (~>) a (f b)). (SFoldable t, SApplicative f) => Sing t -> Sing t -> Sing (Apply (Apply For_Sym0 t) t :: f ()) Source #

type family SequenceA_ (a :: t (f a)) :: f () where ... Source #

Equations

SequenceA_ a_6989586621680438228 = Apply (Apply (Apply FoldrSym0 (*>@#@$)) (Apply PureSym0 Tuple0Sym0)) a_6989586621680438228 

sSequenceA_ :: forall t f a (t :: t (f a)). (SFoldable t, SApplicative f) => Sing t -> Sing (Apply SequenceA_Sym0 t :: f ()) Source #

type family Asum (a :: t (f a)) :: f a where ... Source #

Equations

Asum a_6989586621680438216 = Apply (Apply (Apply FoldrSym0 (<|>@#@$)) EmptySym0) a_6989586621680438216 

sAsum :: forall t f a (t :: t (f a)). (SFoldable t, SAlternative f) => Sing t -> Sing (Apply AsumSym0 t :: f a) Source #

type family MapM_ (a :: (~>) a (m b)) (a :: t a) :: m () where ... Source #

Equations

MapM_ f a_6989586621680438245 = Apply (Apply (Apply FoldrSym0 (Apply (Apply (.@#@$) (>>@#@$)) f)) (Apply ReturnSym0 Tuple0Sym0)) a_6989586621680438245 

sMapM_ :: forall a m b t (t :: (~>) a (m b)) (t :: t a). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing (Apply (Apply MapM_Sym0 t) t :: m ()) Source #

type family ForM_ (a :: t a) (a :: (~>) a (m b)) :: m () where ... Source #

Equations

ForM_ a_6989586621680438234 a_6989586621680438236 = Apply (Apply (Apply FlipSym0 MapM_Sym0) a_6989586621680438234) a_6989586621680438236 

sForM_ :: forall t a m b (t :: t a) (t :: (~>) a (m b)). (SFoldable t, SMonad m) => Sing t -> Sing t -> Sing (Apply (Apply ForM_Sym0 t) t :: m ()) Source #

type family Sequence_ (a :: t (m a)) :: m () where ... Source #

Equations

Sequence_ a_6989586621680438222 = Apply (Apply (Apply FoldrSym0 (>>@#@$)) (Apply ReturnSym0 Tuple0Sym0)) a_6989586621680438222 

sSequence_ :: forall t m a (t :: t (m a)). (SFoldable t, SMonad m) => Sing t -> Sing (Apply Sequence_Sym0 t :: m ()) Source #

type family Msum (a :: t (m a)) :: m a where ... Source #

Equations

Msum a_6989586621680438210 = Apply AsumSym0 a_6989586621680438210 

sMsum :: forall t m a (t :: t (m a)). (SFoldable t, SMonadPlus m) => Sing t -> Sing (Apply MsumSym0 t :: m a) Source #

type family Concat (a :: t [a]) :: [a] where ... Source #

Equations

Concat xs = Apply (Apply (Apply FoldrSym0 (Apply Lambda_6989586621680438205Sym0 xs)) NilSym0) xs 

sConcat :: forall t a (t :: t [a]). SFoldable t => Sing t -> Sing (Apply ConcatSym0 t :: [a]) Source #

type family ConcatMap (a :: (~>) a [b]) (a :: t a) :: [b] where ... Source #

Equations

ConcatMap f xs = Apply (Apply (Apply FoldrSym0 (Apply (Apply Lambda_6989586621680438196Sym0 f) xs)) NilSym0) xs 

sConcatMap :: forall a b t (t :: (~>) a [b]) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply ConcatMapSym0 t) t :: [b]) Source #

type family And (a :: t Bool) :: Bool where ... Source #

Equations

And a_6989586621680438183 = Apply (Apply (Apply (.@#@$) GetAllSym0) (Apply FoldMapSym0 All_Sym0)) a_6989586621680438183 

sAnd :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply AndSym0 t :: Bool) Source #

type family Or (a :: t Bool) :: Bool where ... Source #

Equations

Or a_6989586621680438177 = Apply (Apply (Apply (.@#@$) GetAnySym0) (Apply FoldMapSym0 Any_Sym0)) a_6989586621680438177 

sOr :: forall t (t :: t Bool). SFoldable t => Sing t -> Sing (Apply OrSym0 t :: Bool) Source #

type family Any (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #

Equations

Any p a_6989586621680438168 = Apply (Apply (Apply (.@#@$) GetAnySym0) (Apply FoldMapSym0 (Apply (Apply (.@#@$) Any_Sym0) p))) a_6989586621680438168 

sAny :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AnySym0 t) t :: Bool) Source #

type family All (a :: (~>) a Bool) (a :: t a) :: Bool where ... Source #

Equations

All p a_6989586621680438159 = Apply (Apply (Apply (.@#@$) GetAllSym0) (Apply FoldMapSym0 (Apply (Apply (.@#@$) All_Sym0) p))) a_6989586621680438159 

sAll :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply AllSym0 t) t :: Bool) Source #

type family MaximumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #

Equations

MaximumBy cmp a_6989586621680438139 = Apply (Apply Foldl1Sym0 (Let6989586621680438148Max'Sym2 cmp a_6989586621680438139)) a_6989586621680438139 

sMaximumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MaximumBySym0 t) t :: a) Source #

type family MinimumBy (a :: (~>) a ((~>) a Ordering)) (a :: t a) :: a where ... Source #

Equations

MinimumBy cmp a_6989586621680438119 = Apply (Apply Foldl1Sym0 (Let6989586621680438128Min'Sym2 cmp a_6989586621680438119)) a_6989586621680438119 

sMinimumBy :: forall a t (t :: (~>) a ((~>) a Ordering)) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply MinimumBySym0 t) t :: a) Source #

type family NotElem (a :: a) (a :: t a) :: Bool where ... Source #

Equations

NotElem x a_6989586621680438110 = Apply (Apply (Apply (.@#@$) NotSym0) (Apply ElemSym0 x)) a_6989586621680438110 

sNotElem :: forall a t (t :: a) (t :: t a). (SFoldable t, SEq a) => Sing t -> Sing t -> Sing (Apply (Apply NotElemSym0 t) t :: Bool) Source #

type family Find (a :: (~>) a Bool) (a :: t a) :: Maybe a where ... Source #

Equations

Find p a_6989586621680438092 = Apply (Apply (Apply (.@#@$) GetFirstSym0) (Apply FoldMapSym0 (Apply (Apply Lambda_6989586621680438101Sym0 p) a_6989586621680438092))) a_6989586621680438092 

sFind :: forall a t (t :: (~>) a Bool) (t :: t a). SFoldable t => Sing t -> Sing t -> Sing (Apply (Apply FindSym0 t) t :: Maybe a) Source #

Defunctionalization symbols

data FoldSym0 :: (~>) (t m) m Source #

Instances

Instances details
(SFoldable t, SMonoid m) => SingI (FoldSym0 :: TyFun (t m) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing FoldSym0

SuppressUnusedWarnings (FoldSym0 :: TyFun (t m) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldSym0 :: TyFun (t m) m -> Type) (a6989586621680438312 :: t m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldSym0 :: TyFun (t m) m -> Type) (a6989586621680438312 :: t m) = Fold a6989586621680438312

type family FoldSym1 (a6989586621680438312 :: t m) :: m where ... Source #

Equations

FoldSym1 a6989586621680438312 = Fold a6989586621680438312 

data FoldMapSym0 :: (~>) ((~>) 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

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) (a6989586621680438316 :: a ~> m) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym0 :: TyFun (a ~> m) (t a ~> m) -> Type) (a6989586621680438316 :: a ~> m) = FoldMapSym1 a6989586621680438316 :: TyFun (t a) m -> Type

data FoldMapSym1 (a6989586621680438316 :: (~>) a m) :: (~>) (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 :: k1). Sing x -> Sing (FoldMapSym1 x)

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

SuppressUnusedWarnings (FoldMapSym1 a6989586621680438316 :: TyFun (t a) m -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym1 a6989586621680438316 :: TyFun (t a) m -> Type) (a6989586621680438317 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldMapSym1 a6989586621680438316 :: TyFun (t a) m -> Type) (a6989586621680438317 :: t a) = FoldMap a6989586621680438316 a6989586621680438317

type family FoldMapSym2 (a6989586621680438316 :: (~>) a m) (a6989586621680438317 :: t a) :: m where ... Source #

Equations

FoldMapSym2 a6989586621680438316 a6989586621680438317 = FoldMap a6989586621680438316 a6989586621680438317 

data FoldrSym0 :: (~>) ((~>) 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

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) (a6989586621680438322 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680438322 :: a ~> (b ~> b)) = FoldrSym1 a6989586621680438322 :: TyFun b (t a ~> b) -> Type

data FoldrSym1 (a6989586621680438322 :: (~>) a ((~>) b b)) :: (~>) 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 :: k1). Sing x -> Sing (FoldrSym1 x)

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

SuppressUnusedWarnings (FoldrSym1 a6989586621680438322 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621680438322 :: TyFun b (t a ~> b) -> Type) (a6989586621680438323 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym1 a6989586621680438322 :: TyFun b (t a ~> b) -> Type) (a6989586621680438323 :: b) = FoldrSym2 a6989586621680438322 a6989586621680438323 :: TyFun (t a) b -> Type

data FoldrSym2 (a6989586621680438322 :: (~>) a ((~>) b b)) (a6989586621680438323 :: b) :: (~>) (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 :: k1). Sing x -> Sing (FoldrSym2 d x)

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 :: k1) (y :: k2). Sing x -> Sing y -> Sing (FoldrSym2 x y)

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

SuppressUnusedWarnings (FoldrSym2 a6989586621680438322 a6989586621680438323 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym2 a6989586621680438322 a6989586621680438323 :: TyFun (t a) b -> Type) (a6989586621680438324 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrSym2 a6989586621680438322 a6989586621680438323 :: TyFun (t a) b -> Type) (a6989586621680438324 :: t a) = Foldr a6989586621680438322 a6989586621680438323 a6989586621680438324

type family FoldrSym3 (a6989586621680438322 :: (~>) a ((~>) b b)) (a6989586621680438323 :: b) (a6989586621680438324 :: t a) :: b where ... Source #

Equations

FoldrSym3 a6989586621680438322 a6989586621680438323 a6989586621680438324 = Foldr a6989586621680438322 a6989586621680438323 a6989586621680438324 

data Foldr'Sym0 :: (~>) ((~>) a ((~>) b b)) ((~>) b ((~>) (t a) b)) Source #

Instances

Instances details
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

SuppressUnusedWarnings (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680438329 :: a ~> (b ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym0 :: TyFun (a ~> (b ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680438329 :: a ~> (b ~> b)) = Foldr'Sym1 a6989586621680438329 :: TyFun b (t a ~> b) -> Type

data Foldr'Sym1 (a6989586621680438329 :: (~>) a ((~>) b b)) :: (~>) b ((~>) (t a) b) Source #

Instances

Instances details
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 :: k1). Sing x -> Sing (Foldr'Sym1 x)

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

SuppressUnusedWarnings (Foldr'Sym1 a6989586621680438329 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym1 a6989586621680438329 :: TyFun b (t a ~> b) -> Type) (a6989586621680438330 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym1 a6989586621680438329 :: TyFun b (t a ~> b) -> Type) (a6989586621680438330 :: b) = Foldr'Sym2 a6989586621680438329 a6989586621680438330 :: TyFun (t a) b -> Type

data Foldr'Sym2 (a6989586621680438329 :: (~>) a ((~>) b b)) (a6989586621680438330 :: b) :: (~>) (t a) b Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (Foldr'Sym2 d x)

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 :: k1) (y :: k2). Sing x -> Sing y -> Sing (Foldr'Sym2 x y)

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

SuppressUnusedWarnings (Foldr'Sym2 a6989586621680438329 a6989586621680438330 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym2 a6989586621680438329 a6989586621680438330 :: TyFun (t a) b -> Type) (a6989586621680438331 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr'Sym2 a6989586621680438329 a6989586621680438330 :: TyFun (t a) b -> Type) (a6989586621680438331 :: t a) = Foldr' a6989586621680438329 a6989586621680438330 a6989586621680438331

type family Foldr'Sym3 (a6989586621680438329 :: (~>) a ((~>) b b)) (a6989586621680438330 :: b) (a6989586621680438331 :: t a) :: b where ... Source #

Equations

Foldr'Sym3 a6989586621680438329 a6989586621680438330 a6989586621680438331 = Foldr' a6989586621680438329 a6989586621680438330 a6989586621680438331 

data FoldlSym0 :: (~>) ((~>) 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

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) (a6989586621680438336 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680438336 :: b ~> (a ~> b)) = FoldlSym1 a6989586621680438336 :: TyFun b (t a ~> b) -> Type

data FoldlSym1 (a6989586621680438336 :: (~>) b ((~>) a b)) :: (~>) 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 :: k1). Sing x -> Sing (FoldlSym1 x)

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

SuppressUnusedWarnings (FoldlSym1 a6989586621680438336 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621680438336 :: TyFun b (t a ~> b) -> Type) (a6989586621680438337 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym1 a6989586621680438336 :: TyFun b (t a ~> b) -> Type) (a6989586621680438337 :: b) = FoldlSym2 a6989586621680438336 a6989586621680438337 :: TyFun (t a) b -> Type

data FoldlSym2 (a6989586621680438336 :: (~>) b ((~>) a b)) (a6989586621680438337 :: b) :: (~>) (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 :: k1). Sing x -> Sing (FoldlSym2 d x)

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 :: k1) (y :: k2). Sing x -> Sing y -> Sing (FoldlSym2 x y)

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

SuppressUnusedWarnings (FoldlSym2 a6989586621680438336 a6989586621680438337 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym2 a6989586621680438336 a6989586621680438337 :: TyFun (t a) b -> Type) (a6989586621680438338 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlSym2 a6989586621680438336 a6989586621680438337 :: TyFun (t a) b -> Type) (a6989586621680438338 :: t a) = Foldl a6989586621680438336 a6989586621680438337 a6989586621680438338

type family FoldlSym3 (a6989586621680438336 :: (~>) b ((~>) a b)) (a6989586621680438337 :: b) (a6989586621680438338 :: t a) :: b where ... Source #

Equations

FoldlSym3 a6989586621680438336 a6989586621680438337 a6989586621680438338 = Foldl a6989586621680438336 a6989586621680438337 a6989586621680438338 

data Foldl'Sym0 :: (~>) ((~>) b ((~>) a b)) ((~>) b ((~>) (t a) b)) Source #

Instances

Instances details
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

SuppressUnusedWarnings (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680438343 :: b ~> (a ~> b)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym0 :: TyFun (b ~> (a ~> b)) (b ~> (t a ~> b)) -> Type) (a6989586621680438343 :: b ~> (a ~> b)) = Foldl'Sym1 a6989586621680438343 :: TyFun b (t a ~> b) -> Type

data Foldl'Sym1 (a6989586621680438343 :: (~>) b ((~>) a b)) :: (~>) b ((~>) (t a) b) Source #

Instances

Instances details
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 :: k1). Sing x -> Sing (Foldl'Sym1 x)

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

SuppressUnusedWarnings (Foldl'Sym1 a6989586621680438343 :: TyFun b (t a ~> b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym1 a6989586621680438343 :: TyFun b (t a ~> b) -> Type) (a6989586621680438344 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym1 a6989586621680438343 :: TyFun b (t a ~> b) -> Type) (a6989586621680438344 :: b) = Foldl'Sym2 a6989586621680438343 a6989586621680438344 :: TyFun (t a) b -> Type

data Foldl'Sym2 (a6989586621680438343 :: (~>) b ((~>) a b)) (a6989586621680438344 :: b) :: (~>) (t a) b Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (Foldl'Sym2 d x)

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 :: k1) (y :: k2). Sing x -> Sing y -> Sing (Foldl'Sym2 x y)

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

SuppressUnusedWarnings (Foldl'Sym2 a6989586621680438343 a6989586621680438344 :: TyFun (t a) b -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym2 a6989586621680438343 a6989586621680438344 :: TyFun (t a) b -> Type) (a6989586621680438345 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl'Sym2 a6989586621680438343 a6989586621680438344 :: TyFun (t a) b -> Type) (a6989586621680438345 :: t a) = Foldl' a6989586621680438343 a6989586621680438344 a6989586621680438345

type family Foldl'Sym3 (a6989586621680438343 :: (~>) b ((~>) a b)) (a6989586621680438344 :: b) (a6989586621680438345 :: t a) :: b where ... Source #

Equations

Foldl'Sym3 a6989586621680438343 a6989586621680438344 a6989586621680438345 = Foldl' a6989586621680438343 a6989586621680438344 a6989586621680438345 

data Foldr1Sym0 :: (~>) ((~>) 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

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) (a6989586621680438349 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680438349 :: a ~> (a ~> a)) = Foldr1Sym1 a6989586621680438349 :: TyFun (t a) a -> Type

data Foldr1Sym1 (a6989586621680438349 :: (~>) a ((~>) a a)) :: (~>) (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 :: k1). Sing x -> Sing (Foldr1Sym1 x)

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

SuppressUnusedWarnings (Foldr1Sym1 a6989586621680438349 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym1 a6989586621680438349 :: TyFun (t a) a -> Type) (a6989586621680438350 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldr1Sym1 a6989586621680438349 :: TyFun (t a) a -> Type) (a6989586621680438350 :: t a) = Foldr1 a6989586621680438349 a6989586621680438350

type family Foldr1Sym2 (a6989586621680438349 :: (~>) a ((~>) a a)) (a6989586621680438350 :: t a) :: a where ... Source #

Equations

Foldr1Sym2 a6989586621680438349 a6989586621680438350 = Foldr1 a6989586621680438349 a6989586621680438350 

data Foldl1Sym0 :: (~>) ((~>) 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

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) (a6989586621680438354 :: a ~> (a ~> a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym0 :: TyFun (a ~> (a ~> a)) (t a ~> a) -> Type) (a6989586621680438354 :: a ~> (a ~> a)) = Foldl1Sym1 a6989586621680438354 :: TyFun (t a) a -> Type

data Foldl1Sym1 (a6989586621680438354 :: (~>) a ((~>) a a)) :: (~>) (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 :: k1). Sing x -> Sing (Foldl1Sym1 x)

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

SuppressUnusedWarnings (Foldl1Sym1 a6989586621680438354 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym1 a6989586621680438354 :: TyFun (t a) a -> Type) (a6989586621680438355 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Foldl1Sym1 a6989586621680438354 :: TyFun (t a) a -> Type) (a6989586621680438355 :: t a) = Foldl1 a6989586621680438354 a6989586621680438355

type family Foldl1Sym2 (a6989586621680438354 :: (~>) a ((~>) a a)) (a6989586621680438355 :: t a) :: a where ... Source #

Equations

Foldl1Sym2 a6989586621680438354 a6989586621680438355 = Foldl1 a6989586621680438354 a6989586621680438355 

data ToListSym0 :: (~>) (t a) [a] Source #

Instances

Instances details
SFoldable t => SingI (ToListSym0 :: TyFun (t a) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing ToListSym0

SuppressUnusedWarnings (ToListSym0 :: TyFun (t a) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (a6989586621680438358 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ToListSym0 :: TyFun (t a) [a] -> Type) (a6989586621680438358 :: t a) = ToList a6989586621680438358

type family ToListSym1 (a6989586621680438358 :: t a) :: [a] where ... Source #

Equations

ToListSym1 a6989586621680438358 = ToList a6989586621680438358 

data NullSym0 :: (~>) (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

SuppressUnusedWarnings (NullSym0 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680438361 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NullSym0 :: TyFun (t a) Bool -> Type) (a6989586621680438361 :: t a) = Null a6989586621680438361

type family NullSym1 (a6989586621680438361 :: t a) :: Bool where ... Source #

Equations

NullSym1 a6989586621680438361 = Null a6989586621680438361 

data LengthSym0 :: (~>) (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

SuppressUnusedWarnings (LengthSym0 :: TyFun (t a) Natural -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680438364 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (LengthSym0 :: TyFun (t a) Natural -> Type) (a6989586621680438364 :: t a) = Length a6989586621680438364

type family LengthSym1 (a6989586621680438364 :: t a) :: Natural where ... Source #

Equations

LengthSym1 a6989586621680438364 = Length a6989586621680438364 

data ElemSym0 :: (~>) 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

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) (a6989586621680438368 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680438368 :: a) = ElemSym1 a6989586621680438368 :: TyFun (t a) Bool -> Type

data ElemSym1 (a6989586621680438368 :: a) :: (~>) (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 :: k1). Sing x -> Sing (ElemSym1 x)

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

SuppressUnusedWarnings (ElemSym1 a6989586621680438368 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621680438368 :: TyFun (t a) Bool -> Type) (a6989586621680438369 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ElemSym1 a6989586621680438368 :: TyFun (t a) Bool -> Type) (a6989586621680438369 :: t a) = Elem a6989586621680438368 a6989586621680438369

type family ElemSym2 (a6989586621680438368 :: a) (a6989586621680438369 :: t a) :: Bool where ... Source #

Equations

ElemSym2 a6989586621680438368 a6989586621680438369 = Elem a6989586621680438368 a6989586621680438369 

data MaximumSym0 :: (~>) (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

SuppressUnusedWarnings (MaximumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680438372 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumSym0 :: TyFun (t a) a -> Type) (a6989586621680438372 :: t a) = Maximum a6989586621680438372

type family MaximumSym1 (a6989586621680438372 :: t a) :: a where ... Source #

Equations

MaximumSym1 a6989586621680438372 = Maximum a6989586621680438372 

data MinimumSym0 :: (~>) (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

SuppressUnusedWarnings (MinimumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680438375 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumSym0 :: TyFun (t a) a -> Type) (a6989586621680438375 :: t a) = Minimum a6989586621680438375

type family MinimumSym1 (a6989586621680438375 :: t a) :: a where ... Source #

Equations

MinimumSym1 a6989586621680438375 = Minimum a6989586621680438375 

data SumSym0 :: (~>) (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

SuppressUnusedWarnings (SumSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621680438378 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SumSym0 :: TyFun (t a) a -> Type) (a6989586621680438378 :: t a) = Sum a6989586621680438378

type family SumSym1 (a6989586621680438378 :: t a) :: a where ... Source #

Equations

SumSym1 a6989586621680438378 = Sum a6989586621680438378 

data ProductSym0 :: (~>) (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

SuppressUnusedWarnings (ProductSym0 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680438381 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ProductSym0 :: TyFun (t a) a -> Type) (a6989586621680438381 :: t a) = Product a6989586621680438381

type family ProductSym1 (a6989586621680438381 :: t a) :: a where ... Source #

Equations

ProductSym1 a6989586621680438381 = Product a6989586621680438381 

data FoldrMSym0 :: (~>) ((~>) a ((~>) b (m b))) ((~>) b ((~>) (t a) (m b))) Source #

Instances

Instances details
(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

SuppressUnusedWarnings (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym0 :: TyFun (a ~> (b ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621680438296 :: 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) (a6989586621680438296 :: a ~> (b ~> m b)) = FoldrMSym1 a6989586621680438296 :: TyFun b (t a ~> m b) -> Type

data FoldrMSym1 (a6989586621680438296 :: (~>) a ((~>) b (m b))) :: (~>) b ((~>) (t a) (m b)) Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (FoldrMSym1 x)

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

SuppressUnusedWarnings (FoldrMSym1 a6989586621680438296 :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym1 a6989586621680438296 :: TyFun b (t a ~> m b) -> Type) (a6989586621680438297 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym1 a6989586621680438296 :: TyFun b (t a ~> m b) -> Type) (a6989586621680438297 :: b) = FoldrMSym2 a6989586621680438296 a6989586621680438297 :: TyFun (t a) (m b) -> Type

data FoldrMSym2 (a6989586621680438296 :: (~>) a ((~>) b (m b))) (a6989586621680438297 :: b) :: (~>) (t a) (m b) Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (FoldrMSym2 d x)

(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 :: k1) (y :: k2). Sing x -> Sing y -> Sing (FoldrMSym2 x y)

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

SuppressUnusedWarnings (FoldrMSym2 a6989586621680438296 a6989586621680438297 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym2 a6989586621680438296 a6989586621680438297 :: TyFun (t a) (m b) -> Type) (a6989586621680438298 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldrMSym2 a6989586621680438296 a6989586621680438297 :: TyFun (t a) (m b) -> Type) (a6989586621680438298 :: t a) = FoldrM a6989586621680438296 a6989586621680438297 a6989586621680438298

type family FoldrMSym3 (a6989586621680438296 :: (~>) a ((~>) b (m b))) (a6989586621680438297 :: b) (a6989586621680438298 :: t a) :: m b where ... Source #

Equations

FoldrMSym3 a6989586621680438296 a6989586621680438297 a6989586621680438298 = FoldrM a6989586621680438296 a6989586621680438297 a6989586621680438298 

data FoldlMSym0 :: (~>) ((~>) b ((~>) a (m b))) ((~>) b ((~>) (t a) (m b))) Source #

Instances

Instances details
(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

SuppressUnusedWarnings (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym0 :: TyFun (b ~> (a ~> m b)) (b ~> (t a ~> m b)) -> Type) (a6989586621680438278 :: 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) (a6989586621680438278 :: b ~> (a ~> m b)) = FoldlMSym1 a6989586621680438278 :: TyFun b (t a ~> m b) -> Type

data FoldlMSym1 (a6989586621680438278 :: (~>) b ((~>) a (m b))) :: (~>) b ((~>) (t a) (m b)) Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (FoldlMSym1 x)

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

SuppressUnusedWarnings (FoldlMSym1 a6989586621680438278 :: TyFun b (t a ~> m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym1 a6989586621680438278 :: TyFun b (t a ~> m b) -> Type) (a6989586621680438279 :: b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym1 a6989586621680438278 :: TyFun b (t a ~> m b) -> Type) (a6989586621680438279 :: b) = FoldlMSym2 a6989586621680438278 a6989586621680438279 :: TyFun (t a) (m b) -> Type

data FoldlMSym2 (a6989586621680438278 :: (~>) b ((~>) a (m b))) (a6989586621680438279 :: b) :: (~>) (t a) (m b) Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (FoldlMSym2 d x)

(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 :: k1) (y :: k2). Sing x -> Sing y -> Sing (FoldlMSym2 x y)

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

SuppressUnusedWarnings (FoldlMSym2 a6989586621680438278 a6989586621680438279 :: TyFun (t a) (m b) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym2 a6989586621680438278 a6989586621680438279 :: TyFun (t a) (m b) -> Type) (a6989586621680438280 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FoldlMSym2 a6989586621680438278 a6989586621680438279 :: TyFun (t a) (m b) -> Type) (a6989586621680438280 :: t a) = FoldlM a6989586621680438278 a6989586621680438279 a6989586621680438280

type family FoldlMSym3 (a6989586621680438278 :: (~>) b ((~>) a (m b))) (a6989586621680438279 :: b) (a6989586621680438280 :: t a) :: m b where ... Source #

Equations

FoldlMSym3 a6989586621680438278 a6989586621680438279 a6989586621680438280 = FoldlM a6989586621680438278 a6989586621680438279 a6989586621680438280 

data Traverse_Sym0 :: (~>) ((~>) a (f b)) ((~>) (t a) (f ())) Source #

Instances

Instances details
(SFoldable t, SApplicative f) => SingI (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621680438270 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym0 :: TyFun (a ~> f b) (t a ~> f ()) -> Type) (a6989586621680438270 :: a ~> f b) = Traverse_Sym1 a6989586621680438270 :: TyFun (t a) (f ()) -> Type

data Traverse_Sym1 (a6989586621680438270 :: (~>) a (f b)) :: (~>) (t a) (f ()) Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (Traverse_Sym1 x)

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

SuppressUnusedWarnings (Traverse_Sym1 a6989586621680438270 :: TyFun (t a) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym1 a6989586621680438270 :: TyFun (t a) (f ()) -> Type) (a6989586621680438271 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Traverse_Sym1 a6989586621680438270 :: TyFun (t a) (f ()) -> Type) (a6989586621680438271 :: t a) = Traverse_ a6989586621680438270 a6989586621680438271

type family Traverse_Sym2 (a6989586621680438270 :: (~>) a (f b)) (a6989586621680438271 :: t a) :: f () where ... Source #

Equations

Traverse_Sym2 a6989586621680438270 a6989586621680438271 = Traverse_ a6989586621680438270 a6989586621680438271 

data For_Sym0 :: (~>) (t a) ((~>) ((~>) a (f b)) (f ())) Source #

Instances

Instances details
(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

SuppressUnusedWarnings (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621680438261 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym0 :: TyFun (t a) ((a ~> f b) ~> f ()) -> Type) (a6989586621680438261 :: t a) = For_Sym1 a6989586621680438261 :: TyFun (a ~> f b) (f ()) -> Type

data For_Sym1 (a6989586621680438261 :: t a) :: (~>) ((~>) a (f b)) (f ()) Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (For_Sym1 x)

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

SuppressUnusedWarnings (For_Sym1 a6989586621680438261 :: TyFun (a ~> f b) (f ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym1 a6989586621680438261 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680438262 :: a ~> f b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (For_Sym1 a6989586621680438261 :: TyFun (a ~> f b) (f ()) -> Type) (a6989586621680438262 :: a ~> f b) = For_ a6989586621680438261 a6989586621680438262

type family For_Sym2 (a6989586621680438261 :: t a) (a6989586621680438262 :: (~>) a (f b)) :: f () where ... Source #

Equations

For_Sym2 a6989586621680438261 a6989586621680438262 = For_ a6989586621680438261 a6989586621680438262 

data SequenceA_Sym0 :: (~>) (t (f a)) (f ()) Source #

Instances

Instances details
(SFoldable t, SApplicative f) => SingI (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> 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

type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621680438232 :: t (f a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (SequenceA_Sym0 :: TyFun (t (f a)) (f ()) -> Type) (a6989586621680438232 :: t (f a)) = SequenceA_ a6989586621680438232

type family SequenceA_Sym1 (a6989586621680438232 :: t (f a)) :: f () where ... Source #

Equations

SequenceA_Sym1 a6989586621680438232 = SequenceA_ a6989586621680438232 

data AsumSym0 :: (~>) (t (f a)) (f a) Source #

Instances

Instances details
(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

SuppressUnusedWarnings (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621680438220 :: t (f a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AsumSym0 :: TyFun (t (f a)) (f a) -> Type) (a6989586621680438220 :: t (f a)) = Asum a6989586621680438220

type family AsumSym1 (a6989586621680438220 :: t (f a)) :: f a where ... Source #

Equations

AsumSym1 a6989586621680438220 = Asum a6989586621680438220 

data MapM_Sym0 :: (~>) ((~>) 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

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) (a6989586621680438250 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym0 :: TyFun (a ~> m b) (t a ~> m ()) -> Type) (a6989586621680438250 :: a ~> m b) = MapM_Sym1 a6989586621680438250 :: TyFun (t a) (m ()) -> Type

data MapM_Sym1 (a6989586621680438250 :: (~>) a (m b)) :: (~>) (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 :: k1). Sing x -> Sing (MapM_Sym1 x)

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

SuppressUnusedWarnings (MapM_Sym1 a6989586621680438250 :: TyFun (t a) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym1 a6989586621680438250 :: TyFun (t a) (m ()) -> Type) (a6989586621680438251 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MapM_Sym1 a6989586621680438250 :: TyFun (t a) (m ()) -> Type) (a6989586621680438251 :: t a) = MapM_ a6989586621680438250 a6989586621680438251

type family MapM_Sym2 (a6989586621680438250 :: (~>) a (m b)) (a6989586621680438251 :: t a) :: m () where ... Source #

Equations

MapM_Sym2 a6989586621680438250 a6989586621680438251 = MapM_ a6989586621680438250 a6989586621680438251 

data ForM_Sym0 :: (~>) (t a) ((~>) ((~>) a (m b)) (m ())) Source #

Instances

Instances details
(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

SuppressUnusedWarnings (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621680438241 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym0 :: TyFun (t a) ((a ~> m b) ~> m ()) -> Type) (a6989586621680438241 :: t a) = ForM_Sym1 a6989586621680438241 :: TyFun (a ~> m b) (m ()) -> Type

data ForM_Sym1 (a6989586621680438241 :: t a) :: (~>) ((~>) a (m b)) (m ()) Source #

Instances

Instances details
(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 :: k1). Sing x -> Sing (ForM_Sym1 x)

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

SuppressUnusedWarnings (ForM_Sym1 a6989586621680438241 :: TyFun (a ~> m b) (m ()) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym1 a6989586621680438241 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680438242 :: a ~> m b) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ForM_Sym1 a6989586621680438241 :: TyFun (a ~> m b) (m ()) -> Type) (a6989586621680438242 :: a ~> m b) = ForM_ a6989586621680438241 a6989586621680438242

type family ForM_Sym2 (a6989586621680438241 :: t a) (a6989586621680438242 :: (~>) a (m b)) :: m () where ... Source #

Equations

ForM_Sym2 a6989586621680438241 a6989586621680438242 = ForM_ a6989586621680438241 a6989586621680438242 

data Sequence_Sym0 :: (~>) (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

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) (a6989586621680438226 :: t (m a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (Sequence_Sym0 :: TyFun (t (m a)) (m ()) -> Type) (a6989586621680438226 :: t (m a)) = Sequence_ a6989586621680438226

type family Sequence_Sym1 (a6989586621680438226 :: t (m a)) :: m () where ... Source #

Equations

Sequence_Sym1 a6989586621680438226 = Sequence_ a6989586621680438226 

data MsumSym0 :: (~>) (t (m a)) (m a) Source #

Instances

Instances details
(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

SuppressUnusedWarnings (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621680438214 :: t (m a)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MsumSym0 :: TyFun (t (m a)) (m a) -> Type) (a6989586621680438214 :: t (m a)) = Msum a6989586621680438214

type family MsumSym1 (a6989586621680438214 :: t (m a)) :: m a where ... Source #

Equations

MsumSym1 a6989586621680438214 = Msum a6989586621680438214 

data ConcatSym0 :: (~>) (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

SuppressUnusedWarnings (ConcatSym0 :: TyFun (t [a]) [a] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680438203 :: t [a]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatSym0 :: TyFun (t [a]) [a] -> Type) (a6989586621680438203 :: t [a]) = Concat a6989586621680438203

type family ConcatSym1 (a6989586621680438203 :: t [a]) :: [a] where ... Source #

Equations

ConcatSym1 a6989586621680438203 = Concat a6989586621680438203 

data ConcatMapSym0 :: (~>) ((~>) 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

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) (a6989586621680438192 :: a ~> [b]) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym0 :: TyFun (a ~> [b]) (t a ~> [b]) -> Type) (a6989586621680438192 :: a ~> [b]) = ConcatMapSym1 a6989586621680438192 :: TyFun (t a) [b] -> Type

data ConcatMapSym1 (a6989586621680438192 :: (~>) a [b]) :: (~>) (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 :: k1). Sing x -> Sing (ConcatMapSym1 x)

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

SuppressUnusedWarnings (ConcatMapSym1 a6989586621680438192 :: TyFun (t a) [b] -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym1 a6989586621680438192 :: TyFun (t a) [b] -> Type) (a6989586621680438193 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (ConcatMapSym1 a6989586621680438192 :: TyFun (t a) [b] -> Type) (a6989586621680438193 :: t a) = ConcatMap a6989586621680438192 a6989586621680438193

type family ConcatMapSym2 (a6989586621680438192 :: (~>) a [b]) (a6989586621680438193 :: t a) :: [b] where ... Source #

Equations

ConcatMapSym2 a6989586621680438192 a6989586621680438193 = ConcatMap a6989586621680438192 a6989586621680438193 

data AndSym0 :: (~>) (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

SuppressUnusedWarnings (AndSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680438187 :: t Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AndSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680438187 :: t Bool) = And a6989586621680438187

type family AndSym1 (a6989586621680438187 :: t Bool) :: Bool where ... Source #

Equations

AndSym1 a6989586621680438187 = And a6989586621680438187 

data OrSym0 :: (~>) (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

SuppressUnusedWarnings (OrSym0 :: TyFun (t Bool) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680438181 :: t Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (OrSym0 :: TyFun (t Bool) Bool -> Type) (a6989586621680438181 :: t Bool) = Or a6989586621680438181

type family OrSym1 (a6989586621680438181 :: t Bool) :: Bool where ... Source #

Equations

OrSym1 a6989586621680438181 = Or a6989586621680438181 

data AnySym0 :: (~>) ((~>) 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

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) (a6989586621680438173 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680438173 :: a ~> Bool) = AnySym1 a6989586621680438173 :: TyFun (t a) Bool -> Type

data AnySym1 (a6989586621680438173 :: (~>) a Bool) :: (~>) (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 :: k1). Sing x -> Sing (AnySym1 x)

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

SuppressUnusedWarnings (AnySym1 a6989586621680438173 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621680438173 :: TyFun (t a) Bool -> Type) (a6989586621680438174 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AnySym1 a6989586621680438173 :: TyFun (t a) Bool -> Type) (a6989586621680438174 :: t a) = Any a6989586621680438173 a6989586621680438174

type family AnySym2 (a6989586621680438173 :: (~>) a Bool) (a6989586621680438174 :: t a) :: Bool where ... Source #

Equations

AnySym2 a6989586621680438173 a6989586621680438174 = Any a6989586621680438173 a6989586621680438174 

data AllSym0 :: (~>) ((~>) 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

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) (a6989586621680438164 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym0 :: TyFun (a ~> Bool) (t a ~> Bool) -> Type) (a6989586621680438164 :: a ~> Bool) = AllSym1 a6989586621680438164 :: TyFun (t a) Bool -> Type

data AllSym1 (a6989586621680438164 :: (~>) a Bool) :: (~>) (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 :: k1). Sing x -> Sing (AllSym1 x)

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

SuppressUnusedWarnings (AllSym1 a6989586621680438164 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621680438164 :: TyFun (t a) Bool -> Type) (a6989586621680438165 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (AllSym1 a6989586621680438164 :: TyFun (t a) Bool -> Type) (a6989586621680438165 :: t a) = All a6989586621680438164 a6989586621680438165

type family AllSym2 (a6989586621680438164 :: (~>) a Bool) (a6989586621680438165 :: t a) :: Bool where ... Source #

Equations

AllSym2 a6989586621680438164 a6989586621680438165 = All a6989586621680438164 a6989586621680438165 

data MaximumBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (t a) a) Source #

Instances

Instances details
SFoldable t => SingI (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

SuppressUnusedWarnings (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680438144 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680438144 :: a ~> (a ~> Ordering)) = MaximumBySym1 a6989586621680438144 :: TyFun (t a) a -> Type

data MaximumBySym1 (a6989586621680438144 :: (~>) a ((~>) a Ordering)) :: (~>) (t a) a Source #

Instances

Instances details
SFoldable t => SingI1 (MaximumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (MaximumBySym1 x)

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

SuppressUnusedWarnings (MaximumBySym1 a6989586621680438144 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym1 a6989586621680438144 :: TyFun (t a) a -> Type) (a6989586621680438145 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MaximumBySym1 a6989586621680438144 :: TyFun (t a) a -> Type) (a6989586621680438145 :: t a) = MaximumBy a6989586621680438144 a6989586621680438145

type family MaximumBySym2 (a6989586621680438144 :: (~>) a ((~>) a Ordering)) (a6989586621680438145 :: t a) :: a where ... Source #

Equations

MaximumBySym2 a6989586621680438144 a6989586621680438145 = MaximumBy a6989586621680438144 a6989586621680438145 

data MinimumBySym0 :: (~>) ((~>) a ((~>) a Ordering)) ((~>) (t a) a) Source #

Instances

Instances details
SFoldable t => SingI (MinimumBySym0 :: 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

type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680438124 :: a ~> (a ~> Ordering)) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym0 :: TyFun (a ~> (a ~> Ordering)) (t a ~> a) -> Type) (a6989586621680438124 :: a ~> (a ~> Ordering)) = MinimumBySym1 a6989586621680438124 :: TyFun (t a) a -> Type

data MinimumBySym1 (a6989586621680438124 :: (~>) a ((~>) a Ordering)) :: (~>) (t a) a Source #

Instances

Instances details
SFoldable t => SingI1 (MinimumBySym1 :: (a ~> (a ~> Ordering)) -> TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (MinimumBySym1 x)

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

SuppressUnusedWarnings (MinimumBySym1 a6989586621680438124 :: TyFun (t a) a -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym1 a6989586621680438124 :: TyFun (t a) a -> Type) (a6989586621680438125 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (MinimumBySym1 a6989586621680438124 :: TyFun (t a) a -> Type) (a6989586621680438125 :: t a) = MinimumBy a6989586621680438124 a6989586621680438125

type family MinimumBySym2 (a6989586621680438124 :: (~>) a ((~>) a Ordering)) (a6989586621680438125 :: t a) :: a where ... Source #

Equations

MinimumBySym2 a6989586621680438124 a6989586621680438125 = MinimumBy a6989586621680438124 a6989586621680438125 

data NotElemSym0 :: (~>) 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

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) (a6989586621680438115 :: a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym0 :: TyFun a (t a ~> Bool) -> Type) (a6989586621680438115 :: a) = NotElemSym1 a6989586621680438115 :: TyFun (t a) Bool -> Type

data NotElemSym1 (a6989586621680438115 :: a) :: (~>) (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 :: k1). Sing x -> Sing (NotElemSym1 x)

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

SuppressUnusedWarnings (NotElemSym1 a6989586621680438115 :: TyFun (t a) Bool -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621680438115 :: TyFun (t a) Bool -> Type) (a6989586621680438116 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (NotElemSym1 a6989586621680438115 :: TyFun (t a) Bool -> Type) (a6989586621680438116 :: t a) = NotElem a6989586621680438115 a6989586621680438116

type family NotElemSym2 (a6989586621680438115 :: a) (a6989586621680438116 :: t a) :: Bool where ... Source #

Equations

NotElemSym2 a6989586621680438115 a6989586621680438116 = NotElem a6989586621680438115 a6989586621680438116 

data FindSym0 :: (~>) ((~>) a Bool) ((~>) (t a) (Maybe a)) Source #

Instances

Instances details
SFoldable t => SingI (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

sing :: Sing FindSym0

SuppressUnusedWarnings (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680438097 :: a ~> Bool) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym0 :: TyFun (a ~> Bool) (t a ~> Maybe a) -> Type) (a6989586621680438097 :: a ~> Bool) = FindSym1 a6989586621680438097 :: TyFun (t a) (Maybe a) -> Type

data FindSym1 (a6989586621680438097 :: (~>) a Bool) :: (~>) (t a) (Maybe a) Source #

Instances

Instances details
SFoldable t => SingI1 (FindSym1 :: (a ~> Bool) -> TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (FindSym1 x)

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

SuppressUnusedWarnings (FindSym1 a6989586621680438097 :: TyFun (t a) (Maybe a) -> Type) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym1 a6989586621680438097 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680438098 :: t a) Source # 
Instance details

Defined in Data.Foldable.Singletons

type Apply (FindSym1 a6989586621680438097 :: TyFun (t a) (Maybe a) -> Type) (a6989586621680438098 :: t a) = Find a6989586621680438097 a6989586621680438098

type family FindSym2 (a6989586621680438097 :: (~>) a Bool) (a6989586621680438098 :: t a) :: Maybe a where ... Source #

Equations

FindSym2 a6989586621680438097 a6989586621680438098 = Find a6989586621680438097 a6989586621680438098