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

Data.Semigroup.Singletons

Description

Defines the promoted version of Semigroup, PSemigroup, and the singleton version, SSemigroup.

Synopsis

Documentation

class PSemigroup a Source #

Associated Types

type (arg :: a) <> (arg1 :: a) :: a infixr 6 Source #

type Sconcat (arg :: NonEmpty a) :: a Source #

type Sconcat (arg :: NonEmpty a) = Apply (Sconcat_6989586621679207895Sym0 :: TyFun (NonEmpty a) a -> Type) arg

Instances

Instances details
PSemigroup All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a1 :: All) <> (a2 :: All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: All) <> (a2 :: All)
type Sconcat (arg :: NonEmpty All) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sconcat (arg :: NonEmpty All)
PSemigroup Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type (a1 :: Any) <> (a2 :: Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type (a1 :: Any) <> (a2 :: Any)
type Sconcat (arg :: NonEmpty Any) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sconcat (arg :: NonEmpty Any)
PSemigroup Void Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type (a1 :: Void) <> (a2 :: Void) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type (a1 :: Void) <> (a2 :: Void)
type Sconcat (arg :: NonEmpty Void) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Sconcat (arg :: NonEmpty Void)
PSemigroup Ordering Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type (a1 :: Ordering) <> (a2 :: Ordering) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type (a1 :: Ordering) <> (a2 :: Ordering)
type Sconcat (arg :: NonEmpty Ordering) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Sconcat (arg :: NonEmpty Ordering)
PSemigroup () Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type (a1 :: ()) <> (a2 :: ()) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type (a1 :: ()) <> (a2 :: ())
type Sconcat (a :: NonEmpty ()) 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

type Sconcat (a :: NonEmpty ())
PSemigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type (a :: Symbol) <> (b :: Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type (a :: Symbol) <> (b :: Symbol) = AppendSymbol a b
type Sconcat (arg :: NonEmpty Symbol) 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sconcat (arg :: NonEmpty Symbol)
PSemigroup (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

PSemigroup (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PSemigroup (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

PSemigroup (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PSemigroup (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PSemigroup (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PSemigroup (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

PSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (Maybe a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup [a] Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (Either a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

PSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (a, b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

PSemigroup (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

class SSemigroup a where Source #

Minimal complete definition

(%<>)

Methods

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

sSconcat :: forall (t :: NonEmpty a). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) t) Source #

default sSconcat :: forall (t :: NonEmpty a). Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) t ~ Apply (Sconcat_6989586621679207895Sym0 :: TyFun (NonEmpty a) a -> Type) t => Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) t) Source #

Instances

Instances details
SSemigroup All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

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

sSconcat :: forall (t :: NonEmpty All). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty All) All -> Type) t) Source #

SSemigroup Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

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

sSconcat :: forall (t :: NonEmpty Any). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Any) Any -> Type) t) Source #

SSemigroup Void Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty Void). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Void) Void -> Type) t) Source #

SSemigroup Ordering Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty Ordering). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Ordering) Ordering -> Type) t) Source #

SSemigroup () Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty ()). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty ()) () -> Type) t) Source #

SSemigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Methods

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

sSconcat :: forall (t :: NonEmpty Symbol). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty Symbol) Symbol -> Type) t) Source #

SSemigroup a => SSemigroup (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (Identity a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Identity a)) (Identity a) -> Type) t) Source #

SSemigroup (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (First a)) (First a) -> Type) t) Source #

SSemigroup (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Last a)) (Last a) -> Type) t) Source #

SSemigroup a => SSemigroup (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (Down a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Down a)) (Down a) -> Type) t) Source #

SSemigroup (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (First a)) (First a) -> Type) t) Source #

SSemigroup (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Last a)) (Last a) -> Type) t) Source #

SOrd a => SSemigroup (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (Max a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Max a)) (Max a) -> Type) t) Source #

SOrd a => SSemigroup (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (Min a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Min a)) (Min a) -> Type) t) Source #

SMonoid m => SSemigroup (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (WrappedMonoid m)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (WrappedMonoid m)) (WrappedMonoid m) -> Type) t) Source #

SSemigroup a => SSemigroup (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

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

sSconcat :: forall (t :: NonEmpty (Dual a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Dual a)) (Dual a) -> Type) t) Source #

SNum a => SSemigroup (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

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

sSconcat :: forall (t :: NonEmpty (Product a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Product a)) (Product a) -> Type) t) Source #

SNum a => SSemigroup (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

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

sSconcat :: forall (t :: NonEmpty (Sum a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Sum a)) (Sum a) -> Type) t) Source #

SSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (NonEmpty a)) (NonEmpty a) -> Type) t) Source #

SSemigroup a => SSemigroup (Maybe a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty (Maybe a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Maybe a)) (Maybe a) -> Type) t) Source #

SSemigroup [a] Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty [a]). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty [a]) [a] -> Type) t) Source #

SSemigroup (Either a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty (Either a b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Either a b)) (Either a b) -> Type) t) Source #

SSemigroup (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (Proxy s)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Proxy s)) (Proxy s) -> Type) t) Source #

SSemigroup b => SSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty (a ~> b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a ~> b)) (a ~> b) -> Type) t) Source #

(SSemigroup a, SSemigroup b) => SSemigroup (a, b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a, b)) (a, b) -> Type) t) Source #

SSemigroup a => SSemigroup (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Methods

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

sSconcat :: forall (t :: NonEmpty (Const a b)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Const a b)) (Const a b) -> Type) t) Source #

(SSemigroup a, SSemigroup b, SSemigroup c) => SSemigroup (a, b, c) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty (a, b, c)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a, b, c)) (a, b, c) -> Type) t) Source #

(SSemigroup a, SSemigroup b, SSemigroup c, SSemigroup d) => SSemigroup (a, b, c, d) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty (a, b, c, d)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a, b, c, d)) (a, b, c, d) -> Type) t) Source #

(SSemigroup a, SSemigroup b, SSemigroup c, SSemigroup d, SSemigroup e) => SSemigroup (a, b, c, d, e) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

(%<>) :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply ((<>@#@$) :: TyFun (a, b, c, d, e) ((a, b, c, d, e) ~> (a, b, c, d, e)) -> Type) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c, d, e)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (a, b, c, d, e)) (a, b, c, d, e) -> Type) t) Source #

type family Sing :: k -> Type #

Instances

Instances details
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple0
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SBool
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SChar
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SSymbol
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SIdentity :: Identity a -> Type
type Sing Source # 
Instance details

Defined in Data.Monoid.Singletons

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Monoid.Singletons

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Ord.Singletons

type Sing = SDown :: Down a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SFirst :: First a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SLast :: Last a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SMax :: Max a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SMin :: Min a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SDual :: Dual a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SProduct :: Product a -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Sing = SSum :: Sum a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SNonEmpty :: NonEmpty a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SMaybe :: Maybe a -> Type
type Sing Source #

A choice of singleton for the kind TYPE rep (for some RuntimeRep rep), an instantiation of which is the famous kind Type.

Conceivably, one could generalize this instance to `Sing @k` for any kind k, and remove all other Sing instances. We don't adopt this design, however, since it is far more convenient in practice to work with explicit singleton values than TypeReps (for instance, TypeReps are more difficult to pattern match on, and require extra runtime checks).

We cannot produce explicit singleton values for everything in TYPE rep, however, since it is an open kind, so we reach for TypeRep in this one particular case.

Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

type Sing = TypeRep :: TYPE rep -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SList :: [a] -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SEither :: Either a b -> Type
type Sing Source # 
Instance details

Defined in Data.Proxy.Singletons

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

Defined in Data.Semigroup.Singletons

type Sing = SArg :: Arg a b -> Type
type Sing 
Instance details

Defined in Data.Singletons

type Sing 
Instance details

Defined in Data.Singletons

type Sing = SLambda :: (k1 ~> k2) -> Type
type Sing 
Instance details

Defined in Data.Singletons.Sigma

type Sing = SSigma :: Sigma s t -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple2 :: (a, b) -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Const.Singletons

type Sing = SConst :: Const a b -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple3 :: (a, b, c) -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Product.Singletons

type Sing = SProduct :: Product f g a -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Sum.Singletons

type Sing = SSum :: Sum f g a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple4 :: (a, b, c, d) -> Type
type Sing Source # 
Instance details

Defined in Data.Functor.Compose.Singletons

type Sing = SCompose :: Compose f g a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple5 :: (a, b, c, d, e) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple6 :: (a, b, c, d, e, f) -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple7 :: (a, b, c, d, e, f, g) -> Type

data SMin (a1 :: Min a) where Source #

Constructors

SMin :: forall a (n :: a). Sing n -> SMin ('Min n) 

Instances

Instances details
SDecide a => TestCoercion (SMin :: Min a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: Min a) (b :: Min a). SMin a0 -> SMin b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SMin :: Min a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a0 :: Min a) (b :: Min a). SMin a0 -> SMin b -> Maybe (a0 :~: b) #

ShowSing a => Show (SMin z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SMin z -> ShowS #

show :: SMin z -> String #

showList :: [SMin z] -> ShowS #

Eq (SMin z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SMin z -> SMin z -> Bool #

(/=) :: SMin z -> SMin z -> Bool #

data SMax (a1 :: Max a) where Source #

Constructors

SMax :: forall a (n :: a). Sing n -> SMax ('Max n) 

Instances

Instances details
SDecide a => TestCoercion (SMax :: Max a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: Max a) (b :: Max a). SMax a0 -> SMax b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SMax :: Max a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a0 :: Max a) (b :: Max a). SMax a0 -> SMax b -> Maybe (a0 :~: b) #

ShowSing a => Show (SMax z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SMax z -> ShowS #

show :: SMax z -> String #

showList :: [SMax z] -> ShowS #

Eq (SMax z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SMax z -> SMax z -> Bool #

(/=) :: SMax z -> SMax z -> Bool #

data SFirst (a1 :: First a) where Source #

Constructors

SFirst :: forall a (n :: a). Sing n -> SFirst ('First n) 

Instances

Instances details
SDecide a => TestCoercion (SFirst :: First a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: First a) (b :: First a). SFirst a0 -> SFirst b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SFirst :: First a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a0 :: First a) (b :: First a). SFirst a0 -> SFirst b -> Maybe (a0 :~: b) #

ShowSing a => Show (SFirst z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SFirst z -> ShowS #

show :: SFirst z -> String #

showList :: [SFirst z] -> ShowS #

Eq (SFirst z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SFirst z -> SFirst z -> Bool #

(/=) :: SFirst z -> SFirst z -> Bool #

data SLast (a1 :: Last a) where Source #

Constructors

SLast :: forall a (n :: a). Sing n -> SLast ('Last n) 

Instances

Instances details
SDecide a => TestCoercion (SLast :: Last a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: Last a) (b :: Last a). SLast a0 -> SLast b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SLast :: Last a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a0 :: Last a) (b :: Last a). SLast a0 -> SLast b -> Maybe (a0 :~: b) #

ShowSing a => Show (SLast z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SLast z -> ShowS #

show :: SLast z -> String #

showList :: [SLast z] -> ShowS #

Eq (SLast z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SLast z -> SLast z -> Bool #

(/=) :: SLast z -> SLast z -> Bool #

data SWrappedMonoid (a :: WrappedMonoid m) where Source #

Constructors

SWrapMonoid :: forall m (n :: m). Sing n -> SWrappedMonoid ('WrapMonoid n) 

Instances

Instances details
SDecide m => TestCoercion (SWrappedMonoid :: WrappedMonoid m -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a :: WrappedMonoid m) (b :: WrappedMonoid m). SWrappedMonoid a -> SWrappedMonoid b -> Maybe (Coercion a b) #

SDecide m => TestEquality (SWrappedMonoid :: WrappedMonoid m -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a :: WrappedMonoid m) (b :: WrappedMonoid m). SWrappedMonoid a -> SWrappedMonoid b -> Maybe (a :~: b) #

ShowSing m => Show (SWrappedMonoid z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Eq (SWrappedMonoid z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

data SDual (a1 :: Dual a) where Source #

Constructors

SDual :: forall a (n :: a). Sing n -> SDual ('Dual n) 

Instances

Instances details
SDecide a => TestCoercion (SDual :: Dual a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: Dual a) (b :: Dual a). SDual a0 -> SDual b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SDual :: Dual a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a0 :: Dual a) (b :: Dual a). SDual a0 -> SDual b -> Maybe (a0 :~: b) #

ShowSing a => Show (SDual z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SDual z -> ShowS #

show :: SDual z -> String #

showList :: [SDual z] -> ShowS #

Eq (SDual z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SDual z -> SDual z -> Bool #

(/=) :: SDual z -> SDual z -> Bool #

data SAll (a :: All) where Source #

Constructors

SAll :: forall (n :: Bool). Sing n -> SAll ('All n) 

Instances

Instances details
SDecide Bool => TestCoercion SAll Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a :: All) (b :: All). SAll a -> SAll b -> Maybe (Coercion a b) #

SDecide Bool => TestEquality SAll Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a :: All) (b :: All). SAll a -> SAll b -> Maybe (a :~: b) #

ShowSing Bool => Show (SAll z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SAll z -> ShowS #

show :: SAll z -> String #

showList :: [SAll z] -> ShowS #

Eq (SAll z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SAll z -> SAll z -> Bool #

(/=) :: SAll z -> SAll z -> Bool #

data SAny (a :: Any) where Source #

Constructors

SAny :: forall (n :: Bool). Sing n -> SAny ('Any n) 

Instances

Instances details
SDecide Bool => TestCoercion SAny Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a :: Any) (b :: Any). SAny a -> SAny b -> Maybe (Coercion a b) #

SDecide Bool => TestEquality SAny Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a :: Any) (b :: Any). SAny a -> SAny b -> Maybe (a :~: b) #

ShowSing Bool => Show (SAny z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SAny z -> ShowS #

show :: SAny z -> String #

showList :: [SAny z] -> ShowS #

Eq (SAny z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SAny z -> SAny z -> Bool #

(/=) :: SAny z -> SAny z -> Bool #

data SSum (a1 :: Sum a) where Source #

Constructors

SSum :: forall a (n :: a). Sing n -> SSum ('Sum n) 

Instances

Instances details
SDecide a => TestCoercion (SSum :: Sum a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: Sum a) (b :: Sum a). SSum a0 -> SSum b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SSum :: Sum a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a0 :: Sum a) (b :: Sum a). SSum a0 -> SSum b -> Maybe (a0 :~: b) #

ShowSing a => Show (SSum z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SSum z -> ShowS #

show :: SSum z -> String #

showList :: [SSum z] -> ShowS #

Eq (SSum z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SSum z -> SSum z -> Bool #

(/=) :: SSum z -> SSum z -> Bool #

data SProduct (a1 :: Product a) where Source #

Constructors

SProduct :: forall a (n :: a). Sing n -> SProduct ('Product n) 

Instances

Instances details
SDecide a => TestCoercion (SProduct :: Product a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: Product a) (b :: Product a). SProduct a0 -> SProduct b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SProduct :: Product a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testEquality :: forall (a0 :: Product a) (b :: Product a). SProduct a0 -> SProduct b -> Maybe (a0 :~: b) #

ShowSing a => Show (SProduct z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SProduct z -> ShowS #

show :: SProduct z -> String #

showList :: [SProduct z] -> ShowS #

Eq (SProduct z) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

(==) :: SProduct z -> SProduct z -> Bool #

(/=) :: SProduct z -> SProduct z -> Bool #

data SArg (a1 :: Arg a b) where Source #

Constructors

SArg :: forall a b (n1 :: a) (n2 :: b). Sing n1 -> Sing n2 -> SArg ('Arg n1 n2) 

Instances

Instances details
(ShowSing a, ShowSing b) => Show (SArg z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SArg z -> ShowS #

show :: SArg z -> String #

showList :: [SArg z] -> ShowS #

Eq (SArg z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

(==) :: SArg z -> SArg z -> Bool #

(/=) :: SArg z -> SArg z -> Bool #

Ord (SArg z) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

compare :: SArg z -> SArg z -> Ordering #

(<) :: SArg z -> SArg z -> Bool #

(<=) :: SArg z -> SArg z -> Bool #

(>) :: SArg z -> SArg z -> Bool #

(>=) :: SArg z -> SArg z -> Bool #

max :: SArg z -> SArg z -> SArg z #

min :: SArg z -> SArg z -> SArg z #

type family GetMin (a1 :: Min a) :: a where ... Source #

Equations

GetMin ('Min field :: Min a) = field 

type family GetMax (a1 :: Max a) :: a where ... Source #

Equations

GetMax ('Max field :: Max a) = field 

type family GetFirst (a1 :: First a) :: a where ... Source #

Equations

GetFirst ('First field :: First a) = field 

type family GetLast (a1 :: Last a) :: a where ... Source #

Equations

GetLast ('Last field :: Last a) = field 

type family UnwrapMonoid (a :: WrappedMonoid m) :: m where ... Source #

Equations

UnwrapMonoid ('WrapMonoid field :: WrappedMonoid m) = field 

type family GetDual (a1 :: Dual a) :: a where ... Source #

Equations

GetDual ('Dual field :: Dual a) = field 

type family GetAll (a :: All) :: Bool where ... Source #

Equations

GetAll ('All field) = field 

type family GetAny (a :: Any) :: Bool where ... Source #

Equations

GetAny ('Any field) = field 

type family GetSum (a1 :: Sum a) :: a where ... Source #

Equations

GetSum ('Sum field :: Sum a) = field 

type family GetProduct (a1 :: Product a) :: a where ... Source #

Equations

GetProduct ('Product field :: Product a) = field 

sGetMin :: forall a (t :: Min a). Sing t -> Sing (Apply (GetMinSym0 :: TyFun (Min a) a -> Type) t) Source #

sGetMax :: forall a (t :: Max a). Sing t -> Sing (Apply (GetMaxSym0 :: TyFun (Max a) a -> Type) t) Source #

sGetFirst :: forall a (t :: First a). Sing t -> Sing (Apply (GetFirstSym0 :: TyFun (First a) a -> Type) t) Source #

sGetLast :: forall a (t :: Last a). Sing t -> Sing (Apply (GetLastSym0 :: TyFun (Last a) a -> Type) t) Source #

sGetDual :: forall a (t :: Dual a). Sing t -> Sing (Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) t) Source #

sGetAll :: forall (t :: All). Sing t -> Sing (Apply GetAllSym0 t) Source #

sGetAny :: forall (t :: Any). Sing t -> Sing (Apply GetAnySym0 t) Source #

sGetSum :: forall a (t :: Sum a). Sing t -> Sing (Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) t) Source #

sGetProduct :: forall a (t :: Product a). Sing t -> Sing (Apply (GetProductSym0 :: TyFun (Product a) a -> Type) t) Source #

Defunctionalization symbols

data (<>@#@$) (a1 :: TyFun a (a ~> a)) infixr 6 Source #

Instances

Instances details
SSemigroup a => SingI ((<>@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing ((<>@#@$) :: TyFun a (a ~> a) -> Type) #

SuppressUnusedWarnings ((<>@#@$) :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$) :: TyFun a (a ~> a) -> Type) (a6989586621679207889 :: a) = (<>@#@$$) a6989586621679207889

data (a6989586621679207889 :: a) <>@#@$$ (b :: TyFun a a) infixr 6 Source #

Instances

Instances details
SSemigroup a => SingI1 ((<>@#@$$) :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

liftSing :: forall (x :: a). Sing x -> Sing ((<>@#@$$) x) #

(SSemigroup a, SingI d) => SingI ((<>@#@$$) d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing ((<>@#@$$) d) #

SuppressUnusedWarnings ((<>@#@$$) a6989586621679207889 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$$) a6989586621679207889 :: TyFun a a -> Type) (a6989586621679207890 :: a) = a6989586621679207889 <> a6989586621679207890

type family (a6989586621679207889 :: a) <>@#@$$$ (a6989586621679207890 :: a) :: a where ... infixr 6 Source #

Equations

(a6989586621679207889 :: a) <>@#@$$$ (a6989586621679207890 :: a) = a6989586621679207889 <> a6989586621679207890 

data SconcatSym0 (a1 :: TyFun (NonEmpty a) a) Source #

Instances

Instances details
SSemigroup a => SingI (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

sing :: Sing (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) #

SuppressUnusedWarnings (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply (SconcatSym0 :: TyFun (NonEmpty a) a -> Type) (a6989586621679207893 :: NonEmpty a) = Sconcat a6989586621679207893

type family SconcatSym1 (a6989586621679207893 :: NonEmpty a) :: a where ... Source #

Equations

SconcatSym1 (a6989586621679207893 :: NonEmpty a) = Sconcat a6989586621679207893 

data MinSym0 (a1 :: TyFun a (Min a)) Source #

Instances

Instances details
SingI (MinSym0 :: TyFun a (Min a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (MinSym0 :: TyFun a (Min a) -> Type) #

SuppressUnusedWarnings (MinSym0 :: TyFun a (Min a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (MinSym0 :: TyFun a (Min a) -> Type) (a6989586621679687620 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (MinSym0 :: TyFun a (Min a) -> Type) (a6989586621679687620 :: a) = 'Min a6989586621679687620

type family MinSym1 (a6989586621679687620 :: a) :: Min a where ... Source #

Equations

MinSym1 (a6989586621679687620 :: a) = 'Min a6989586621679687620 

data GetMinSym0 (a1 :: TyFun (Min a) a) Source #

Instances

Instances details
SingI (GetMinSym0 :: TyFun (Min a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetMinSym0 :: TyFun (Min a) a -> Type) #

SuppressUnusedWarnings (GetMinSym0 :: TyFun (Min a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetMinSym0 :: TyFun (Min a) a -> Type) (a6989586621679687623 :: Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetMinSym0 :: TyFun (Min a) a -> Type) (a6989586621679687623 :: Min a) = GetMin a6989586621679687623

type family GetMinSym1 (a6989586621679687623 :: Min a) :: a where ... Source #

Equations

GetMinSym1 (a6989586621679687623 :: Min a) = GetMin a6989586621679687623 

data MaxSym0 (a1 :: TyFun a (Max a)) Source #

Instances

Instances details
SingI (MaxSym0 :: TyFun a (Max a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (MaxSym0 :: TyFun a (Max a) -> Type) #

SuppressUnusedWarnings (MaxSym0 :: TyFun a (Max a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (MaxSym0 :: TyFun a (Max a) -> Type) (a6989586621679687639 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (MaxSym0 :: TyFun a (Max a) -> Type) (a6989586621679687639 :: a) = 'Max a6989586621679687639

type family MaxSym1 (a6989586621679687639 :: a) :: Max a where ... Source #

Equations

MaxSym1 (a6989586621679687639 :: a) = 'Max a6989586621679687639 

data GetMaxSym0 (a1 :: TyFun (Max a) a) Source #

Instances

Instances details
SingI (GetMaxSym0 :: TyFun (Max a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetMaxSym0 :: TyFun (Max a) a -> Type) #

SuppressUnusedWarnings (GetMaxSym0 :: TyFun (Max a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetMaxSym0 :: TyFun (Max a) a -> Type) (a6989586621679687642 :: Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetMaxSym0 :: TyFun (Max a) a -> Type) (a6989586621679687642 :: Max a) = GetMax a6989586621679687642

type family GetMaxSym1 (a6989586621679687642 :: Max a) :: a where ... Source #

Equations

GetMaxSym1 (a6989586621679687642 :: Max a) = GetMax a6989586621679687642 

data FirstSym0 (a1 :: TyFun a (First a)) Source #

Instances

Instances details
SingI (FirstSym0 :: TyFun a (First a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (FirstSym0 :: TyFun a (First a) -> Type) #

SuppressUnusedWarnings (FirstSym0 :: TyFun a (First a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (FirstSym0 :: TyFun a (First a) -> Type) (a6989586621679687658 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (FirstSym0 :: TyFun a (First a) -> Type) (a6989586621679687658 :: a) = 'First a6989586621679687658

type family FirstSym1 (a6989586621679687658 :: a) :: First a where ... Source #

Equations

FirstSym1 (a6989586621679687658 :: a) = 'First a6989586621679687658 

data GetFirstSym0 (a1 :: TyFun (First a) a) Source #

Instances

Instances details
SingI (GetFirstSym0 :: TyFun (First a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetFirstSym0 :: TyFun (First a) a -> Type) #

SuppressUnusedWarnings (GetFirstSym0 :: TyFun (First a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetFirstSym0 :: TyFun (First a) a -> Type) (a6989586621679687661 :: First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetFirstSym0 :: TyFun (First a) a -> Type) (a6989586621679687661 :: First a) = GetFirst a6989586621679687661

type family GetFirstSym1 (a6989586621679687661 :: First a) :: a where ... Source #

Equations

GetFirstSym1 (a6989586621679687661 :: First a) = GetFirst a6989586621679687661 

data LastSym0 (a1 :: TyFun a (Last a)) Source #

Instances

Instances details
SingI (LastSym0 :: TyFun a (Last a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (LastSym0 :: TyFun a (Last a) -> Type) #

SuppressUnusedWarnings (LastSym0 :: TyFun a (Last a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (LastSym0 :: TyFun a (Last a) -> Type) (a6989586621679687677 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (LastSym0 :: TyFun a (Last a) -> Type) (a6989586621679687677 :: a) = 'Last a6989586621679687677

type family LastSym1 (a6989586621679687677 :: a) :: Last a where ... Source #

Equations

LastSym1 (a6989586621679687677 :: a) = 'Last a6989586621679687677 

data GetLastSym0 (a1 :: TyFun (Last a) a) Source #

Instances

Instances details
SingI (GetLastSym0 :: TyFun (Last a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetLastSym0 :: TyFun (Last a) a -> Type) #

SuppressUnusedWarnings (GetLastSym0 :: TyFun (Last a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetLastSym0 :: TyFun (Last a) a -> Type) (a6989586621679687680 :: Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetLastSym0 :: TyFun (Last a) a -> Type) (a6989586621679687680 :: Last a) = GetLast a6989586621679687680

type family GetLastSym1 (a6989586621679687680 :: Last a) :: a where ... Source #

Equations

GetLastSym1 (a6989586621679687680 :: Last a) = GetLast a6989586621679687680 

data WrapMonoidSym0 (a :: TyFun m (WrappedMonoid m)) Source #

Instances

Instances details
SingI (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) #

SuppressUnusedWarnings (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) (a6989586621679687696 :: m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (WrapMonoidSym0 :: TyFun m (WrappedMonoid m) -> Type) (a6989586621679687696 :: m) = 'WrapMonoid a6989586621679687696

type family WrapMonoidSym1 (a6989586621679687696 :: m) :: WrappedMonoid m where ... Source #

Equations

WrapMonoidSym1 (a6989586621679687696 :: m) = 'WrapMonoid a6989586621679687696 

data UnwrapMonoidSym0 (a :: TyFun (WrappedMonoid m) m) Source #

Instances

Instances details
SingI (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SuppressUnusedWarnings (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) (a6989586621679687699 :: WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) (a6989586621679687699 :: WrappedMonoid m) = UnwrapMonoid a6989586621679687699

type family UnwrapMonoidSym1 (a6989586621679687699 :: WrappedMonoid m) :: m where ... Source #

Equations

UnwrapMonoidSym1 (a6989586621679687699 :: WrappedMonoid m) = UnwrapMonoid a6989586621679687699 

data DualSym0 (a1 :: TyFun a (Dual a)) Source #

Instances

Instances details
SingI (DualSym0 :: TyFun a (Dual a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (DualSym0 :: TyFun a (Dual a) -> Type) #

SuppressUnusedWarnings (DualSym0 :: TyFun a (Dual a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (DualSym0 :: TyFun a (Dual a) -> Type) (a6989586621679687531 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (DualSym0 :: TyFun a (Dual a) -> Type) (a6989586621679687531 :: a) = 'Dual a6989586621679687531

type family DualSym1 (a6989586621679687531 :: a) :: Dual a where ... Source #

Equations

DualSym1 (a6989586621679687531 :: a) = 'Dual a6989586621679687531 

data GetDualSym0 (a1 :: TyFun (Dual a) a) Source #

Instances

Instances details
SingI (GetDualSym0 :: TyFun (Dual a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetDualSym0 :: TyFun (Dual a) a -> Type) #

SuppressUnusedWarnings (GetDualSym0 :: TyFun (Dual a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679687534 :: Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679687534 :: Dual a) = GetDual a6989586621679687534

type family GetDualSym1 (a6989586621679687534 :: Dual a) :: a where ... Source #

Equations

GetDualSym1 (a6989586621679687534 :: Dual a) = GetDual a6989586621679687534 

data AllSym0 (a :: TyFun Bool All) Source #

Instances

Instances details
SingI AllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing AllSym0 #

SuppressUnusedWarnings AllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply AllSym0 (a6989586621679687547 :: Bool) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply AllSym0 (a6989586621679687547 :: Bool) = 'All a6989586621679687547

type family AllSym1 (a6989586621679687547 :: Bool) :: All where ... Source #

Equations

AllSym1 a6989586621679687547 = 'All a6989586621679687547 

data GetAllSym0 (a :: TyFun All Bool) Source #

Instances

Instances details
SingI GetAllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing GetAllSym0 #

SuppressUnusedWarnings GetAllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply GetAllSym0 (a6989586621679687550 :: All) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply GetAllSym0 (a6989586621679687550 :: All) = GetAll a6989586621679687550

type family GetAllSym1 (a6989586621679687550 :: All) :: Bool where ... Source #

Equations

GetAllSym1 a6989586621679687550 = GetAll a6989586621679687550 

data AnySym0 (a :: TyFun Bool Any) Source #

Instances

Instances details
SingI AnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing AnySym0 #

SuppressUnusedWarnings AnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply AnySym0 (a6989586621679687563 :: Bool) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply AnySym0 (a6989586621679687563 :: Bool) = 'Any a6989586621679687563

type family AnySym1 (a6989586621679687563 :: Bool) :: Any where ... Source #

Equations

AnySym1 a6989586621679687563 = 'Any a6989586621679687563 

data GetAnySym0 (a :: TyFun Any Bool) Source #

Instances

Instances details
SingI GetAnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing GetAnySym0 #

SuppressUnusedWarnings GetAnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply GetAnySym0 (a6989586621679687566 :: Any) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply GetAnySym0 (a6989586621679687566 :: Any) = GetAny a6989586621679687566

type family GetAnySym1 (a6989586621679687566 :: Any) :: Bool where ... Source #

Equations

GetAnySym1 a6989586621679687566 = GetAny a6989586621679687566 

data SumSym0 (a1 :: TyFun a (Sum a)) Source #

Instances

Instances details
SingI (SumSym0 :: TyFun a (Sum a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (SumSym0 :: TyFun a (Sum a) -> Type) #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (SumSym0 :: TyFun a (Sum a) -> Type) (a6989586621679687582 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (SumSym0 :: TyFun a (Sum a) -> Type) (a6989586621679687582 :: a) = 'Sum a6989586621679687582

type family SumSym1 (a6989586621679687582 :: a) :: Sum a where ... Source #

Equations

SumSym1 (a6989586621679687582 :: a) = 'Sum a6989586621679687582 

data GetSumSym0 (a1 :: TyFun (Sum a) a) Source #

Instances

Instances details
SingI (GetSumSym0 :: TyFun (Sum a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetSumSym0 :: TyFun (Sum a) a -> Type) #

SuppressUnusedWarnings (GetSumSym0 :: TyFun (Sum a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679687585 :: Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679687585 :: Sum a) = GetSum a6989586621679687585

type family GetSumSym1 (a6989586621679687585 :: Sum a) :: a where ... Source #

Equations

GetSumSym1 (a6989586621679687585 :: Sum a) = GetSum a6989586621679687585 

data ProductSym0 (a1 :: TyFun a (Product a)) Source #

Instances

Instances details
SingI (ProductSym0 :: TyFun a (Product a) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (ProductSym0 :: TyFun a (Product a) -> Type) #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (ProductSym0 :: TyFun a (Product a) -> Type) (a6989586621679687601 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (ProductSym0 :: TyFun a (Product a) -> Type) (a6989586621679687601 :: a) = 'Product a6989586621679687601

type family ProductSym1 (a6989586621679687601 :: a) :: Product a where ... Source #

Equations

ProductSym1 (a6989586621679687601 :: a) = 'Product a6989586621679687601 

data GetProductSym0 (a1 :: TyFun (Product a) a) Source #

Instances

Instances details
SingI (GetProductSym0 :: TyFun (Product a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

sing :: Sing (GetProductSym0 :: TyFun (Product a) a -> Type) #

SuppressUnusedWarnings (GetProductSym0 :: TyFun (Product a) a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679687604 :: Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679687604 :: Product a) = GetProduct a6989586621679687604

type family GetProductSym1 (a6989586621679687604 :: Product a) :: a where ... Source #

Equations

GetProductSym1 (a6989586621679687604 :: Product a) = GetProduct a6989586621679687604 

data ArgSym0 (a1 :: TyFun a (b ~> Arg a b)) Source #

Instances

Instances details
SingI (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sing :: Sing (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) #

SuppressUnusedWarnings (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680862528 :: a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (ArgSym0 :: TyFun a (b ~> Arg a b) -> Type) (a6989586621680862528 :: a) = ArgSym1 a6989586621680862528 :: TyFun b (Arg a b) -> Type

data ArgSym1 (a6989586621680862528 :: a) (b1 :: TyFun b (Arg a b)) Source #

Instances

Instances details
SingI1 (ArgSym1 :: a -> TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ArgSym1 x :: TyFun b (Arg a b) -> Type) #

SingI d => SingI (ArgSym1 d :: TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sing :: Sing (ArgSym1 d :: TyFun b (Arg a b) -> Type) #

SuppressUnusedWarnings (ArgSym1 a6989586621680862528 :: TyFun b (Arg a b) -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (ArgSym1 a6989586621680862528 :: TyFun b (Arg a b) -> Type) (a6989586621680862529 :: b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

type Apply (ArgSym1 a6989586621680862528 :: TyFun b (Arg a b) -> Type) (a6989586621680862529 :: b) = 'Arg a6989586621680862528 a6989586621680862529

type family ArgSym2 (a6989586621680862528 :: a) (a6989586621680862529 :: b) :: Arg a b where ... Source #

Equations

ArgSym2 (a6989586621680862528 :: a) (a6989586621680862529 :: b) = 'Arg a6989586621680862528 a6989586621680862529 

Orphan instances

PApplicative First Source # 
Instance details

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a :: k1)
type (a2 :: First (a1 ~> b)) <*> (a3 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: First (a1 ~> b)) <*> (a3 :: First a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: First a1) (a4 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: First a1) (a4 :: First b)
type (a2 :: First a1) *> (a3 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: First a1) *> (a3 :: First b)
type (a2 :: First a1) <* (a3 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: First a1) <* (a3 :: First b)
PApplicative Last Source # 
Instance details

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a :: k1)
type (a2 :: Last (a1 ~> b)) <*> (a3 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Last (a1 ~> b)) <*> (a3 :: Last a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Last a1) (a4 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Last a1) (a4 :: Last b)
type (a2 :: Last a1) *> (a3 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Last a1) *> (a3 :: Last b)
type (a2 :: Last a1) <* (a3 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Last a1) <* (a3 :: Last b)
PApplicative Max Source # 
Instance details

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a :: k1)
type (a2 :: Max (a1 ~> b)) <*> (a3 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Max (a1 ~> b)) <*> (a3 :: Max a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Max a1) (a4 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Max a1) (a4 :: Max b)
type (a2 :: Max a1) *> (a3 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Max a1) *> (a3 :: Max b)
type (a2 :: Max a1) <* (a3 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Max a1) <* (a3 :: Max b)
PApplicative Min Source # 
Instance details

Associated Types

type Pure (a :: k1) 
Instance details

Defined in Data.Semigroup.Singletons

type Pure (a :: k1)
type (a2 :: Min (a1 ~> b)) <*> (a3 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Min (a1 ~> b)) <*> (a3 :: Min a1)
type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Min a1) (a4 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type LiftA2 (a2 :: a1 ~> (b ~> c)) (a3 :: Min a1) (a4 :: Min b)
type (a2 :: Min a1) *> (a3 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Min a1) *> (a3 :: Min b)
type (a2 :: Min a1) <* (a3 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a2 :: Min a1) <* (a3 :: Min b)
PFunctor First Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: First a1)
type (a1 :: k1) <$ (a2 :: First b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: First b)
PFunctor Last Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Last a1)
type (a1 :: k1) <$ (a2 :: Last b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: Last b)
PFunctor Max Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Max a1)
type (a1 :: k1) <$ (a2 :: Max b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: Max b)
PFunctor Min Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

type Fmap (a2 :: a1 ~> b) (a3 :: Min a1)
type (a1 :: k1) <$ (a2 :: Min b) 
Instance details

Defined in Data.Semigroup.Singletons

type (a1 :: k1) <$ (a2 :: Min b)
PMonad First Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type (a2 :: First a1) >> (a3 :: First b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons

type Return (arg :: a)
PMonad Last Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type (a2 :: Last a1) >> (a3 :: Last b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons

type Return (arg :: a)
PMonad Max Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type (a2 :: Max a1) >> (a3 :: Max b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons

type Return (arg :: a)
PMonad Min Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type (a2 :: Min a1) >> (a3 :: Min b)
type Return (arg :: a) 
Instance details

Defined in Data.Semigroup.Singletons

type Return (arg :: a)
SApplicative First Source # 
Instance details

Methods

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

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

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: First a) (t3 :: First b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (First a ~> (First b ~> First c)) -> Type) t1) t2) t3) Source #

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

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

SApplicative Last Source # 
Instance details

Methods

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

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

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Last a) (t3 :: Last b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Last a ~> (Last b ~> Last c)) -> Type) t1) t2) t3) Source #

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

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

SApplicative Max Source # 
Instance details

Methods

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

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

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Max a) (t3 :: Max b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Max a ~> (Max b ~> Max c)) -> Type) t1) t2) t3) Source #

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

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

SApplicative Min Source # 
Instance details

Methods

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

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

sLiftA2 :: forall a b c (t1 :: a ~> (b ~> c)) (t2 :: Min a) (t3 :: Min b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (LiftA2Sym0 :: TyFun (a ~> (b ~> c)) (Min a ~> (Min b ~> Min c)) -> Type) t1) t2) t3) Source #

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

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

SFunctor First Source # 
Instance details

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (First a ~> First b) -> Type) t1) t2) Source #

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

SFunctor Last Source # 
Instance details

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Last a ~> Last b) -> Type) t1) t2) Source #

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

SFunctor Max Source # 
Instance details

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Max a ~> Max b) -> Type) t1) t2) Source #

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

SFunctor Min Source # 
Instance details

Methods

sFmap :: forall a b (t1 :: a ~> b) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Min a ~> Min b) -> Type) t1) t2) Source #

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

SMonad First Source # 
Instance details

Methods

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

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

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

SMonad Last Source # 
Instance details

Methods

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

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

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

SMonad Max Source # 
Instance details

Methods

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

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

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

SMonad Min Source # 
Instance details

Methods

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

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

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

PFoldable First Source # 
Instance details

Associated Types

type Fold (arg :: First m) 
Instance details

Defined in Data.Semigroup.Singletons

type Fold (arg :: First m)
type FoldMap (a2 :: a1 ~> k2) (a3 :: First a1) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: First a1)
type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: First a)
type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a)
type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: First a)
type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: First a)
type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: First a)
type ToList (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type ToList (arg :: First a)
type Null (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: First a)
type Length (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: First a)
type Elem (arg :: a) (arg1 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Elem (arg :: a) (arg1 :: First a)
type Maximum (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Minimum (arg :: First a)
type Sum (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Sum (arg :: First a)
type Product (arg :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type Product (arg :: First a)
PFoldable Last Source # 
Instance details

Associated Types

type Fold (arg :: Last m) 
Instance details

Defined in Data.Semigroup.Singletons

type Fold (arg :: Last m)
type FoldMap (a2 :: a1 ~> k2) (a3 :: Last a1) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Last a1)
type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Last a)
type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a)
type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Last a)
type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Last a)
type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Last a)
type ToList (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type ToList (arg :: Last a)
type Null (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Last a)
type Length (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Last a)
type Elem (arg :: a) (arg1 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Elem (arg :: a) (arg1 :: Last a)
type Maximum (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Minimum (arg :: Last a)
type Sum (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Sum (arg :: Last a)
type Product (arg :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type Product (arg :: Last a)
PFoldable Max Source # 
Instance details

Associated Types

type Fold (arg :: Max m) 
Instance details

Defined in Data.Semigroup.Singletons

type Fold (arg :: Max m)
type FoldMap (a2 :: a1 ~> k2) (a3 :: Max a1) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Max a1)
type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Max a)
type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a)
type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Max a)
type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Max a)
type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Max a)
type ToList (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type ToList (arg :: Max a)
type Null (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Max a)
type Length (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Max a)
type Elem (arg :: a) (arg1 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Elem (arg :: a) (arg1 :: Max a)
type Maximum (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Minimum (arg :: Max a)
type Sum (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Sum (arg :: Max a)
type Product (arg :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type Product (arg :: Max a)
PFoldable Min Source # 
Instance details

Associated Types

type Fold (arg :: Min m) 
Instance details

Defined in Data.Semigroup.Singletons

type Fold (arg :: Min m)
type FoldMap (a2 :: a1 ~> k2) (a3 :: Min a1) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Foldr (a2 :: a1 ~> (k2 ~> k2)) (a3 :: k2) (a4 :: Min a1)
type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr' (arg :: a ~> (b ~> b)) (arg1 :: b) (arg2 :: Min a)
type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a)
type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl' (arg :: b ~> (a ~> b)) (arg1 :: b) (arg2 :: Min a)
type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldr1 (arg :: a ~> (a ~> a)) (arg1 :: Min a)
type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Foldl1 (arg :: a ~> (a ~> a)) (arg1 :: Min a)
type ToList (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type ToList (arg :: Min a)
type Null (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Null (arg :: Min a)
type Length (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Length (arg :: Min a)
type Elem (arg :: a) (arg1 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Elem (arg :: a) (arg1 :: Min a)
type Maximum (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Minimum (arg :: Min a)
type Sum (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Sum (arg :: Min a)
type Product (arg :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type Product (arg :: Min a)
SFoldable First Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Last Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Max Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Min Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

PTraversable First Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: First a1)
type SequenceA (arg :: First (f a)) 
Instance details

Defined in Data.Semigroup.Singletons

type SequenceA (arg :: First (f a))
type MapM (arg :: a ~> m b) (arg1 :: First a) 
Instance details

Defined in Data.Semigroup.Singletons

type MapM (arg :: a ~> m b) (arg1 :: First a)
type Sequence (arg :: First (m a)) 
Instance details

Defined in Data.Semigroup.Singletons

type Sequence (arg :: First (m a))
PTraversable Last Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Last a1)
type SequenceA (arg :: Last (f a)) 
Instance details

Defined in Data.Semigroup.Singletons

type SequenceA (arg :: Last (f a))
type MapM (arg :: a ~> m b) (arg1 :: Last a) 
Instance details

Defined in Data.Semigroup.Singletons

type MapM (arg :: a ~> m b) (arg1 :: Last a)
type Sequence (arg :: Last (m a)) 
Instance details

Defined in Data.Semigroup.Singletons

type Sequence (arg :: Last (m a))
PTraversable Max Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Max a1)
type SequenceA (arg :: Max (f a)) 
Instance details

Defined in Data.Semigroup.Singletons

type SequenceA (arg :: Max (f a))
type MapM (arg :: a ~> m b) (arg1 :: Max a) 
Instance details

Defined in Data.Semigroup.Singletons

type MapM (arg :: a ~> m b) (arg1 :: Max a)
type Sequence (arg :: Max (m a)) 
Instance details

Defined in Data.Semigroup.Singletons

type Sequence (arg :: Max (m a))
PTraversable Min Source # 
Instance details

Associated Types

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

Defined in Data.Semigroup.Singletons

type Traverse (a2 :: a1 ~> f b) (a3 :: Min a1)
type SequenceA (arg :: Min (f a)) 
Instance details

Defined in Data.Semigroup.Singletons

type SequenceA (arg :: Min (f a))
type MapM (arg :: a ~> m b) (arg1 :: Min a) 
Instance details

Defined in Data.Semigroup.Singletons

type MapM (arg :: a ~> m b) (arg1 :: Min a)
type Sequence (arg :: Min (m a)) 
Instance details

Defined in Data.Semigroup.Singletons

type Sequence (arg :: Min (m a))
STraversable First Source # 
Instance details

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: First a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (First a ~> f (First b)) -> Type) t1) t2) Source #

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

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

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

STraversable Last Source # 
Instance details

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Last a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Last a ~> f (Last b)) -> Type) t1) t2) Source #

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

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

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

STraversable Max Source # 
Instance details

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Max a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Max a ~> f (Max b)) -> Type) t1) t2) Source #

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

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

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

STraversable Min Source # 
Instance details

Methods

sTraverse :: forall a (f :: Type -> Type) b (t1 :: a ~> f b) (t2 :: Min a). SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Min a ~> f (Min b)) -> Type) t1) t2) Source #

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

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

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

PShow All Source # 
Instance details

Associated Types

type ShowsPrec a1 (a2 :: All) a3 
Instance details

Defined in Data.Semigroup.Singletons

type ShowsPrec a1 (a2 :: All) a3
type Show_ (arg :: All) 
Instance details

Defined in Data.Semigroup.Singletons

type Show_ (arg :: All)
type ShowList (arg :: [All]) arg1 
Instance details

Defined in Data.Semigroup.Singletons

type ShowList (arg :: [All]) arg1
PShow Any Source # 
Instance details

Associated Types

type ShowsPrec a1 (a2 :: Any) a3 
Instance details

Defined in Data.Semigroup.Singletons

type ShowsPrec a1 (a2 :: Any) a3
type Show_ (arg :: Any) 
Instance details

Defined in Data.Semigroup.Singletons

type Show_ (arg :: Any)
type ShowList (arg :: [Any]) arg1 
Instance details

Defined in Data.Semigroup.Singletons

type ShowList (arg :: [Any]) arg1
SShow Bool => SShow All Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: All) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (All ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [All]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [All] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow Bool => SShow Any Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Any) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Any ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Any]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Any] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SingI2 ('Arg :: k1 -> k2 -> Arg k1 k2) Source # 
Instance details

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing ('Arg x y) #

SingI n => SingI1 ('Arg n :: k1 -> Arg a k1) Source # 
Instance details

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Arg n x) #

ShowSing Bool => Show (SAll z) Source # 
Instance details

Methods

showsPrec :: Int -> SAll z -> ShowS #

show :: SAll z -> String #

showList :: [SAll z] -> ShowS #

ShowSing Bool => Show (SAny z) Source # 
Instance details

Methods

showsPrec :: Int -> SAny z -> ShowS #

show :: SAny z -> String #

showList :: [SAny z] -> ShowS #

PFunctor (Arg a) Source # 
Instance details

SFunctor (Arg a) Source # 
Instance details

Methods

sFmap :: forall a0 b (t1 :: a0 ~> b) (t2 :: Arg a a0). Sing t1 -> Sing t2 -> Sing (Apply (Apply (FmapSym0 :: TyFun (a ~> b) (Arg a a ~> Arg a b) -> Type) t1) t2) Source #

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

PFoldable (Arg a) Source # 
Instance details

SFoldable (Arg a) Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

sProduct :: forall a0 (t1 :: Arg a a0). SNum a0 => Sing t1 -> Sing (Apply (ProductSym0 :: TyFun (Arg a a) a -> Type) t1) Source #

PMonoid (Max a) Source # 
Instance details

Associated Types

type Mempty 
Instance details

Defined in Data.Semigroup.Singletons

type Mempty
PMonoid (Min a) Source # 
Instance details

Associated Types

type Mempty 
Instance details

Defined in Data.Semigroup.Singletons

type Mempty
PMonoid (WrappedMonoid m) Source # 
Instance details

Associated Types

type Mempty 
Instance details

Defined in Data.Semigroup.Singletons

type Mempty
(SOrd a, SBounded a) => SMonoid (Max a) Source # 
Instance details

Methods

sMempty :: Sing (MemptySym0 :: Max a) Source #

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

sMconcat :: forall (t :: [Max a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Max a] (Max a) -> Type) t) Source #

(SOrd a, SBounded a) => SMonoid (Min a) Source # 
Instance details

Methods

sMempty :: Sing (MemptySym0 :: Min a) Source #

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

sMconcat :: forall (t :: [Min a]). Sing t -> Sing (Apply (MconcatSym0 :: TyFun [Min a] (Min a) -> Type) t) Source #

SMonoid m => SMonoid (WrappedMonoid m) Source # 
Instance details

PSemigroup (First a) Source # 
Instance details

PSemigroup (Last a) Source # 
Instance details

PSemigroup (Max a) Source # 
Instance details

PSemigroup (Min a) Source # 
Instance details

PSemigroup (WrappedMonoid m) Source # 
Instance details

SSemigroup (First a) Source # 
Instance details

Methods

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

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (First a)) (First a) -> Type) t) Source #

SSemigroup (Last a) Source # 
Instance details

Methods

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

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Last a)) (Last a) -> Type) t) Source #

SOrd a => SSemigroup (Max a) Source # 
Instance details

Methods

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

sSconcat :: forall (t :: NonEmpty (Max a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Max a)) (Max a) -> Type) t) Source #

SOrd a => SSemigroup (Min a) Source # 
Instance details

Methods

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

sSconcat :: forall (t :: NonEmpty (Min a)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (Min a)) (Min a) -> Type) t) Source #

SMonoid m => SSemigroup (WrappedMonoid m) Source # 
Instance details

Methods

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

sSconcat :: forall (t :: NonEmpty (WrappedMonoid m)). Sing t -> Sing (Apply (SconcatSym0 :: TyFun (NonEmpty (WrappedMonoid m)) (WrappedMonoid m) -> Type) t) Source #

PEnum (First a) Source # 
Instance details

PEnum (Last a) Source # 
Instance details

PEnum (Max a) Source # 
Instance details

PEnum (Min a) Source # 
Instance details

PEnum (WrappedMonoid a) Source # 
Instance details

SEnum a => SEnum (First a) Source # 
Instance details

Methods

sSucc :: forall (t :: First a). Sing t -> Sing (Apply (SuccSym0 :: TyFun (First a) (First a) -> Type) t) Source #

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

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

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

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

sEnumFromThenTo :: forall (t1 :: First a) (t2 :: First a) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (First a) (First a ~> (First a ~> [First a])) -> Type) t1) t2) t3) Source #

SEnum a => SEnum (Last a) Source # 
Instance details

Methods

sSucc :: forall (t :: Last a). Sing t -> Sing (Apply (SuccSym0 :: TyFun (Last a) (Last a) -> Type) t) Source #

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

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

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

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

sEnumFromThenTo :: forall (t1 :: Last a) (t2 :: Last a) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Last a) (Last a ~> (Last a ~> [Last a])) -> Type) t1) t2) t3) Source #

SEnum a => SEnum (Max a) Source # 
Instance details

Methods

sSucc :: forall (t :: Max a). Sing t -> Sing (Apply (SuccSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

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

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

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

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

sEnumFromThenTo :: forall (t1 :: Max a) (t2 :: Max a) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Max a) (Max a ~> (Max a ~> [Max a])) -> Type) t1) t2) t3) Source #

SEnum a => SEnum (Min a) Source # 
Instance details

Methods

sSucc :: forall (t :: Min a). Sing t -> Sing (Apply (SuccSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

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

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

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

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

sEnumFromThenTo :: forall (t1 :: Min a) (t2 :: Min a) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (Min a) (Min a ~> (Min a ~> [Min a])) -> Type) t1) t2) t3) Source #

SEnum a => SEnum (WrappedMonoid a) Source # 
Instance details

Methods

sSucc :: forall (t :: WrappedMonoid a). Sing t -> Sing (Apply (SuccSym0 :: TyFun (WrappedMonoid a) (WrappedMonoid a) -> Type) t) Source #

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

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

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

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

sEnumFromThenTo :: forall (t1 :: WrappedMonoid a) (t2 :: WrappedMonoid a) (t3 :: WrappedMonoid a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (EnumFromThenToSym0 :: TyFun (WrappedMonoid a) (WrappedMonoid a ~> (WrappedMonoid a ~> [WrappedMonoid a])) -> Type) t1) t2) t3) Source #

PTraversable (Arg a) Source # 
Instance details

STraversable (Arg a) Source # 
Instance details

Methods

sTraverse :: forall a0 (f :: Type -> Type) b (t1 :: a0 ~> f b) (t2 :: Arg a a0). SApplicative f => Sing t1 -> Sing t2 -> Sing (Apply (Apply (TraverseSym0 :: TyFun (a ~> f b) (Arg a a ~> f (Arg a b)) -> Type) t1) t2) Source #

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

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

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

PNum (Max a) Source # 
Instance details

PNum (Min a) Source # 
Instance details

SNum a => SNum (Max a) Source # 
Instance details

Methods

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

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

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

sNegate :: forall (t :: Max a). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

sAbs :: forall (t :: Max a). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

sSignum :: forall (t :: Max a). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Max a) (Max a) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Max a) -> Type) t) Source #

SNum a => SNum (Min a) Source # 
Instance details

Methods

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

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

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

sNegate :: forall (t :: Min a). Sing t -> Sing (Apply (NegateSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

sAbs :: forall (t :: Min a). Sing t -> Sing (Apply (AbsSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

sSignum :: forall (t :: Min a). Sing t -> Sing (Apply (SignumSym0 :: TyFun (Min a) (Min a) -> Type) t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply (FromIntegerSym0 :: TyFun Natural (Min a) -> Type) t) Source #

PShow (First a) Source # 
Instance details

PShow (Last a) Source # 
Instance details

PShow (Max a) Source # 
Instance details

PShow (Min a) Source # 
Instance details

PShow (WrappedMonoid m) Source # 
Instance details

PShow (Dual a) Source # 
Instance details

PShow (Product a) Source # 
Instance details

PShow (Sum a) Source # 
Instance details

SShow a => SShow (First a) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: First a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (First a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [First a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow a => SShow (Last a) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Last a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Last a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Last a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow a => SShow (Max a) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Max a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Max a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Max a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Max a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow a => SShow (Min a) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Min a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Min a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Min a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Min a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow m => SShow (WrappedMonoid m) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: WrappedMonoid m) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (WrappedMonoid m ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [WrappedMonoid m]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [WrappedMonoid m] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow a => SShow (Dual a) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Dual a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Dual a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Dual a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Dual a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow a => SShow (Product a) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Product a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Product a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Product a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Product a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow a => SShow (Sum a) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Sum a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Sum a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Sum a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Sum a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

ShowSing a => Show (SDual z) Source # 
Instance details

Methods

showsPrec :: Int -> SDual z -> ShowS #

show :: SDual z -> String #

showList :: [SDual z] -> ShowS #

ShowSing a => Show (SFirst z) Source # 
Instance details

Methods

showsPrec :: Int -> SFirst z -> ShowS #

show :: SFirst z -> String #

showList :: [SFirst z] -> ShowS #

ShowSing a => Show (SLast z) Source # 
Instance details

Methods

showsPrec :: Int -> SLast z -> ShowS #

show :: SLast z -> String #

showList :: [SLast z] -> ShowS #

ShowSing a => Show (SMax z) Source # 
Instance details

Methods

showsPrec :: Int -> SMax z -> ShowS #

show :: SMax z -> String #

showList :: [SMax z] -> ShowS #

ShowSing a => Show (SMin z) Source # 
Instance details

Methods

showsPrec :: Int -> SMin z -> ShowS #

show :: SMin z -> String #

showList :: [SMin z] -> ShowS #

ShowSing a => Show (SProduct z) Source # 
Instance details

Methods

showsPrec :: Int -> SProduct z -> ShowS #

show :: SProduct z -> String #

showList :: [SProduct z] -> ShowS #

ShowSing a => Show (SSum z) Source # 
Instance details

Methods

showsPrec :: Int -> SSum z -> ShowS #

show :: SSum z -> String #

showList :: [SSum z] -> ShowS #

ShowSing m => Show (SWrappedMonoid z) Source # 
Instance details

(SingKind a, SingKind b) => SingKind (Arg a b) Source # 
Instance details

Associated Types

type Demote (Arg a b) 
Instance details

Defined in Data.Semigroup.Singletons

type Demote (Arg a b) = Arg (Demote a) (Demote b)

Methods

fromSing :: forall (a0 :: Arg a b). Sing a0 -> Demote (Arg a b) #

toSing :: Demote (Arg a b) -> SomeSing (Arg a b) #

PEq (Arg a b) Source # 
Instance details

SEq a => SEq (Arg a b) Source # 
Instance details

Methods

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

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

POrd (Arg a b) Source # 
Instance details

SOrd a => SOrd (Arg a b) Source # 
Instance details

Methods

sCompare :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (CompareSym0 :: TyFun (Arg a b) (Arg a b ~> Ordering) -> Type) t1) t2) Source #

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

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

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

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

sMax :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MaxSym0 :: TyFun (Arg a b) (Arg a b ~> Arg a b) -> Type) t1) t2) Source #

sMin :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (MinSym0 :: TyFun (Arg a b) (Arg a b ~> Arg a b) -> Type) t1) t2) Source #

PShow (Arg a b) Source # 
Instance details

(SShow a, SShow b) => SShow (Arg a b) Source # 
Instance details

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Arg a b) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Arg a b ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Arg a b). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Arg a b) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Arg a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Arg a b] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Methods

sing :: Sing ('Arg n1 n2) #