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

Data.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) <> (arg :: a) :: a infixr 6 Source #

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

type Sconcat a = Apply Sconcat_6989586621679166901Sym0 a

Instances

Instances details
PSemigroup All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup Void Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup Ordering Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup () Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup Symbol Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Down a) Source # 
Instance details

Defined in Data.Ord.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Maybe a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup [a] Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Either a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (a, b) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Semigroup.Singletons.Internal.Classes

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

class SSemigroup a where Source #

Minimal complete definition

(%<>)

Methods

(%<>) :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t :: a) :: Type infixr 6 Source #

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

default sSconcat :: forall (t :: NonEmpty a). (Apply SconcatSym0 t :: a) ~ Apply Sconcat_6989586621679166901Sym0 t => Sing t -> Sing (Apply SconcatSym0 t :: a) :: Type 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty All). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty Any). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty Void). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

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

SSemigroup () Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

Methods

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

sSconcat :: forall (t :: NonEmpty ()). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty Symbol). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Identity a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Down a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (First a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Max a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Min a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (WrappedMonoid m)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Dual a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Product a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Sum a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (NonEmpty a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Maybe a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty [a]). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Either a b)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Proxy s)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a ~> b)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Const a b)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (a, b, c, d)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

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

type family Sing :: k -> Type #

The singleton kind-indexed type family.

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 = SWrappedMonoid :: WrappedMonoid m -> Type
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Singletons.Base.Instances

type Sing = 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 = SWrappedSing :: WrappedSing a -> Type
type Sing 
Instance details

Defined in Data.Singletons

type Sing = SLambda :: (k1 ~> k2) -> 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 :: forall (a :: Type). Min a -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: k) (b :: k). 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 :: k) (b :: k). SMin a0 -> SMin b -> Maybe (a0 :~: b)

ShowSing a => Show (SMin z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SMin z -> ShowS

show :: SMin z -> String

showList :: [SMin z] -> ShowS

data SMax :: forall (a :: Type). Max a -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: k) (b :: k). 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 :: k) (b :: k). SMax a0 -> SMax b -> Maybe (a0 :~: b)

ShowSing a => Show (SMax z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SMax z -> ShowS

show :: SMax z -> String

showList :: [SMax z] -> ShowS

data SFirst :: forall (a :: Type). First a -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: k) (b :: k). 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 :: k) (b :: k). SFirst a0 -> SFirst b -> Maybe (a0 :~: b)

ShowSing a => Show (SFirst z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SFirst z -> ShowS

show :: SFirst z -> String

showList :: [SFirst z] -> ShowS

data SLast :: forall (a :: Type). Last a -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: k) (b :: k). 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 :: k) (b :: k). SLast a0 -> SLast b -> Maybe (a0 :~: b)

ShowSing a => Show (SLast z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SLast z -> ShowS

show :: SLast z -> String

showList :: [SLast z] -> ShowS

data SWrappedMonoid :: forall (m :: Type). WrappedMonoid m -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a :: k) (b :: k). 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 :: k) (b :: k). SWrappedMonoid a -> SWrappedMonoid b -> Maybe (a :~: b)

ShowSing m => Show (SWrappedMonoid z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SWrappedMonoid z -> ShowS

show :: SWrappedMonoid z -> String

showList :: [SWrappedMonoid z] -> ShowS

data SDual :: forall (a :: Type). Dual a -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: k) (b :: k). 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 :: k) (b :: k). SDual a0 -> SDual b -> Maybe (a0 :~: b)

ShowSing a => Show (SDual z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SDual z -> ShowS

show :: SDual z -> String

showList :: [SDual z] -> ShowS

data SAll :: All -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a :: k) (b :: k). 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 :: k) (b :: k). SAll a -> SAll b -> Maybe (a :~: b)

ShowSing Bool => Show (SAll z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SAll z -> ShowS

show :: SAll z -> String

showList :: [SAll z] -> ShowS

data SAny :: Any -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a :: k) (b :: k). 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 :: k) (b :: k). SAny a -> SAny b -> Maybe (a :~: b)

ShowSing Bool => Show (SAny z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SAny z -> ShowS

show :: SAny z -> String

showList :: [SAny z] -> ShowS

data SSum :: forall (a :: Type). Sum a -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: k) (b :: k). 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 :: k) (b :: k). SSum a0 -> SSum b -> Maybe (a0 :~: b)

ShowSing a => Show (SSum z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SSum z -> ShowS

show :: SSum z -> String

showList :: [SSum z] -> ShowS

data SProduct :: forall (a :: Type). Product a -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Methods

testCoercion :: forall (a0 :: k) (b :: k). 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 :: k) (b :: k). SProduct a0 -> SProduct b -> Maybe (a0 :~: b)

ShowSing a => Show (SProduct z) 
Instance details

Defined in Data.Semigroup.Singletons

Methods

showsPrec :: Int -> SProduct z -> ShowS

show :: SProduct z -> String

showList :: [SProduct z] -> ShowS

data SArg :: forall (a :: Type) (b :: Type). Arg a b -> Type where Source #

Constructors

SArg :: forall (a :: Type) (b :: Type) (n :: a) (n :: b). (Sing n) -> (Sing n) -> SArg ('Arg n n :: Arg (a :: Type) (b :: Type)) 

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

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

Equations

GetMin ('Min field) = field 

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

Equations

GetMax ('Max field) = field 

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

Equations

GetFirst ('First field) = field 

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

Equations

GetLast ('Last field) = field 

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

Equations

UnwrapMonoid ('WrapMonoid field) = field 

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

Equations

GetDual ('Dual field) = 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 (a :: Sum (a :: Type)) :: a where ... Source #

Equations

GetSum ('Sum field) = field 

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

Equations

GetProduct ('Product field) = field 

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

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

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

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

sUnwrapMonoid :: forall (m :: Type) (t :: WrappedMonoid (m :: Type)). Sing t -> Sing (Apply UnwrapMonoidSym0 t :: m) Source #

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

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

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

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

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

Defunctionalization symbols

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

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

data (<>@#@$$) (a6989586621679166895 :: a) :: (~>) 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 :: k1). 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 ((<>@#@$$) a6989586621679166895 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Classes

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

Defined in Data.Semigroup.Singletons.Internal.Classes

type Apply ((<>@#@$$) a6989586621679166895 :: TyFun a a -> Type) (a6989586621679166896 :: a) = a6989586621679166895 <> a6989586621679166896

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

Equations

a6989586621679166895 <>@#@$$$ a6989586621679166896 = (<>) a6989586621679166895 a6989586621679166896 

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

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

Defined in Data.Semigroup.Singletons.Internal.Classes

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

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

Equations

SconcatSym1 a6989586621679166899 = Sconcat a6989586621679166899 

data MinSym0 :: (~>) a (Min (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

MinSym1 a6989586621679553406 = 'Min a6989586621679553406 

data GetMinSym0 :: (~>) (Min (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetMinSym1 a6989586621679553409 = GetMin a6989586621679553409 

data MaxSym0 :: (~>) a (Max (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

MaxSym1 a6989586621679553425 = 'Max a6989586621679553425 

data GetMaxSym0 :: (~>) (Max (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetMaxSym1 a6989586621679553428 = GetMax a6989586621679553428 

data FirstSym0 :: (~>) a (First (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

FirstSym1 a6989586621679553444 = 'First a6989586621679553444 

data GetFirstSym0 :: (~>) (First (a :: Type)) a Source #

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetFirstSym1 a6989586621679553447 = GetFirst a6989586621679553447 

data LastSym0 :: (~>) a (Last (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

LastSym1 a6989586621679553463 = 'Last a6989586621679553463 

data GetLastSym0 :: (~>) (Last (a :: Type)) a Source #

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetLastSym1 a6989586621679553466 = GetLast a6989586621679553466 

data WrapMonoidSym0 :: (~>) m (WrappedMonoid (m :: Type)) Source #

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

WrapMonoidSym1 a6989586621679553482 = 'WrapMonoid a6989586621679553482 

data UnwrapMonoidSym0 :: (~>) (WrappedMonoid (m :: Type)) 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) (a6989586621679553485 :: WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

UnwrapMonoidSym1 a6989586621679553485 = UnwrapMonoid a6989586621679553485 

data DualSym0 :: (~>) a (Dual (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

DualSym1 a6989586621679553316 = 'Dual a6989586621679553316 

data GetDualSym0 :: (~>) (Dual (a :: Type)) a Source #

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetDualSym1 a6989586621679553319 = GetDual a6989586621679553319 

data AllSym0 :: (~>) 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 (a6989586621679553333 :: Bool) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

AllSym1 a6989586621679553333 = 'All a6989586621679553333 

data GetAllSym0 :: (~>) 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 (a6989586621679553336 :: All) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetAllSym1 a6989586621679553336 = GetAll a6989586621679553336 

data AnySym0 :: (~>) 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 (a6989586621679553349 :: Bool) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

AnySym1 a6989586621679553349 = 'Any a6989586621679553349 

data GetAnySym0 :: (~>) 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 (a6989586621679553352 :: Any) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetAnySym1 a6989586621679553352 = GetAny a6989586621679553352 

data SumSym0 :: (~>) a (Sum (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

SumSym1 a6989586621679553368 = 'Sum a6989586621679553368 

data GetSumSym0 :: (~>) (Sum (a :: Type)) 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 #

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetSumSym1 a6989586621679553371 = GetSum a6989586621679553371 

data ProductSym0 :: (~>) a (Product (a :: Type)) Source #

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

ProductSym1 a6989586621679553387 = 'Product a6989586621679553387 

data GetProductSym0 :: (~>) (Product (a :: Type)) a Source #

Instances

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

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

Equations

GetProductSym1 a6989586621679553390 = GetProduct a6989586621679553390 

data ArgSym0 :: (~>) a ((~>) b (Arg (a :: Type) (b :: Type))) 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 #

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

Defined in Data.Semigroup.Singletons

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

data ArgSym1 (a6989586621680480794 :: a) :: (~>) b (Arg (a :: Type) (b :: Type)) 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 :: k1). Sing x -> Sing (ArgSym1 x) #

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

Defined in Data.Semigroup.Singletons

Methods

sing :: Sing (ArgSym1 d) #

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

Defined in Data.Semigroup.Singletons

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

Defined in Data.Semigroup.Singletons

type Apply (ArgSym1 a6989586621680480794 :: TyFun b (Arg a b) -> Type) (a6989586621680480795 :: b) = 'Arg a6989586621680480794 a6989586621680480795

type family ArgSym2 (a6989586621680480794 :: a) (a6989586621680480795 :: b) :: Arg (a :: Type) (b :: Type) where ... Source #

Equations

ArgSym2 a6989586621680480794 a6989586621680480795 = 'Arg a6989586621680480794 a6989586621680480795 

Orphan instances

PApplicative First Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

type arg <*> arg1 :: f b Source #

type LiftA2 arg arg1 arg2 :: f c Source #

type arg *> arg1 :: f b Source #

type arg <* arg1 :: f a Source #

PApplicative Last Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

type arg <*> arg1 :: f b Source #

type LiftA2 arg arg1 arg2 :: f c Source #

type arg *> arg1 :: f b Source #

type arg <* arg1 :: f a Source #

PApplicative Max Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

type arg <*> arg1 :: f b Source #

type LiftA2 arg arg1 arg2 :: f c Source #

type arg *> arg1 :: f b Source #

type arg <* arg1 :: f a Source #

PApplicative Min Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

type arg <*> arg1 :: f b Source #

type LiftA2 arg arg1 arg2 :: f c Source #

type arg *> arg1 :: f b Source #

type arg <* arg1 :: f a Source #

PFunctor First Source # 
Instance details

Associated Types

type Fmap arg arg1 :: f b Source #

type arg <$ arg1 :: f a Source #

PFunctor Last Source # 
Instance details

Associated Types

type Fmap arg arg1 :: f b Source #

type arg <$ arg1 :: f a Source #

PFunctor Max Source # 
Instance details

Associated Types

type Fmap arg arg1 :: f b Source #

type arg <$ arg1 :: f a Source #

PFunctor Min Source # 
Instance details

Associated Types

type Fmap arg arg1 :: f b Source #

type arg <$ arg1 :: f a Source #

PMonad First Source # 
Instance details

Associated Types

type arg >>= arg1 :: m b Source #

type arg >> arg1 :: m b Source #

type Return arg :: m a Source #

PMonad Last Source # 
Instance details

Associated Types

type arg >>= arg1 :: m b Source #

type arg >> arg1 :: m b Source #

type Return arg :: m a Source #

PMonad Max Source # 
Instance details

Associated Types

type arg >>= arg1 :: m b Source #

type arg >> arg1 :: m b Source #

type Return arg :: m a Source #

PMonad Min Source # 
Instance details

Associated Types

type arg >>= arg1 :: m b Source #

type arg >> arg1 :: m b Source #

type Return arg :: m a Source #

SApplicative First Source # 
Instance details

Methods

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

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

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

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

SApplicative Last Source # 
Instance details

Methods

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

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

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

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

SApplicative Max Source # 
Instance details

Methods

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

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

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

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

SApplicative Min Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

sReturn :: forall a (t :: a). Sing t -> Sing (Apply ReturnSym0 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 (>>=@#@$) t1) t2) Source #

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

sReturn :: forall a (t :: a). Sing t -> Sing (Apply ReturnSym0 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 (>>=@#@$) t1) t2) Source #

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

sReturn :: forall a (t :: a). Sing t -> Sing (Apply ReturnSym0 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 (>>=@#@$) t1) t2) Source #

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

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

PFoldable First Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Last Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Max Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Min Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

SFoldable First Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Last Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Max Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Min Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

PTraversable First Source # 
Instance details

Associated Types

type Traverse arg arg1 :: f (t b) Source #

type SequenceA arg :: f (t a) Source #

type MapM arg arg1 :: m (t b) Source #

type Sequence arg :: m (t a) Source #

PTraversable Last Source # 
Instance details

Associated Types

type Traverse arg arg1 :: f (t b) Source #

type SequenceA arg :: f (t a) Source #

type MapM arg arg1 :: m (t b) Source #

type Sequence arg :: m (t a) Source #

PTraversable Max Source # 
Instance details

Associated Types

type Traverse arg arg1 :: f (t b) Source #

type SequenceA arg :: f (t a) Source #

type MapM arg arg1 :: m (t b) Source #

type Sequence arg :: m (t a) Source #

PTraversable Min Source # 
Instance details

Associated Types

type Traverse arg arg1 :: f (t b) Source #

type SequenceA arg :: f (t a) Source #

type MapM arg arg1 :: m (t b) Source #

type Sequence arg :: m (t a) Source #

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 t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: First (f a)). SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 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 t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: First (m a)). SMonad m => Sing t1 -> Sing (Apply SequenceSym0 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 t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Last (f a)). SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 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 t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Last (m a)). SMonad m => Sing t1 -> Sing (Apply SequenceSym0 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 t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Max (f a)). SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 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 t1) t2) Source #

sSequence :: forall (m :: Type -> Type) a (t1 :: Max (m a)). SMonad m => Sing t1 -> Sing (Apply SequenceSym0 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 t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a (t1 :: Min (f a)). SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 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 t1) t2) Source #

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

PShow All Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow Any Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

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 t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [All]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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 t1) t2) t3) Source #

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

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

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

Methods

liftSing2 :: forall (x :: k10) (y :: k20). Sing x -> Sing y -> Sing ('Arg x y) #

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

Methods

liftSing :: forall (x :: k10). 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

Associated Types

type Fmap arg arg1 :: f b Source #

type arg <$ arg1 :: f a Source #

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 t1) t2) Source #

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

PFoldable (Arg a) Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg1 :: m Source #

type Foldr arg arg1 arg2 :: b Source #

type Foldr' arg arg1 arg2 :: b Source #

type Foldl arg arg1 arg2 :: b Source #

type Foldl' arg arg1 arg2 :: b Source #

type Foldr1 arg arg1 :: a Source #

type Foldl1 arg arg1 :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Natural Source #

type Elem arg arg1 :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

SFoldable (Arg a) Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

PMonoid (Max a) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Min a) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (WrappedMonoid m) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

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

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Methods

sMempty :: Sing MemptySym0 Source #

sMappend :: forall (t1 :: WrappedMonoid m) (t2 :: WrappedMonoid m). Sing t1 -> Sing t2 -> Sing (Apply (Apply MappendSym0 t1) t2) Source #

sMconcat :: forall (t :: [WrappedMonoid m]). Sing t -> Sing (Apply MconcatSym0 t) Source #

PSemigroup (First a) Source # 
Instance details

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Max a) Source # 
Instance details

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Min a) Source # 
Instance details

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (WrappedMonoid m) Source # 
Instance details

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

SSemigroup (First a) Source # 
Instance details

Methods

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

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

SSemigroup (Last a) Source # 
Instance details

Methods

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

sSconcat :: forall (t :: NonEmpty (Last a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Max a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

sSconcat :: forall (t :: NonEmpty (Min a)). Sing t -> Sing (Apply SconcatSym0 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 (<>@#@$) t1) t2) Source #

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

PEnum (First a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

type EnumFromThenTo arg arg1 arg2 :: [a] Source #

PEnum (Last a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

type EnumFromThenTo arg arg1 arg2 :: [a] Source #

PEnum (Max a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

type EnumFromThenTo arg arg1 arg2 :: [a] Source #

PEnum (Min a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

type EnumFromThenTo arg arg1 arg2 :: [a] Source #

PEnum (WrappedMonoid a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

type EnumFromThenTo arg arg1 arg2 :: [a] Source #

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

Methods

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

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

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 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 t1) t2) t3) Source #

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

Methods

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

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

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 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 t1) t2) t3) Source #

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

Methods

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

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

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t1 :: Max a) (t2 :: Max a). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 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 t1) t2) t3) Source #

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

Methods

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

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

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t1 :: Min a) (t2 :: Min a). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 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 t1) t2) t3) Source #

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

Methods

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

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

sToEnum :: forall (t :: Natural). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t1 :: WrappedMonoid a) (t2 :: WrappedMonoid a). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 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 t1) t2) t3) Source #

PTraversable (Arg a) Source # 
Instance details

Associated Types

type Traverse arg arg1 :: f (t b) Source #

type SequenceA arg :: f (t a) Source #

type MapM arg arg1 :: m (t b) Source #

type Sequence arg :: m (t a) Source #

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 t1) t2) Source #

sSequenceA :: forall (f :: Type -> Type) a0 (t1 :: Arg a (f a0)). SApplicative f => Sing t1 -> Sing (Apply SequenceASym0 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 t1) t2) Source #

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

PNum (Max a) Source # 
Instance details

Associated Types

type arg + arg1 :: a Source #

type arg - arg1 :: a Source #

type arg * arg1 :: a Source #

type Negate arg :: a Source #

type Abs arg :: a Source #

type Signum arg :: a Source #

type FromInteger arg :: a Source #

PNum (Min a) Source # 
Instance details

Associated Types

type arg + arg1 :: a Source #

type arg - arg1 :: a Source #

type arg * arg1 :: a Source #

type Negate arg :: a Source #

type Abs arg :: a Source #

type Signum arg :: a Source #

type FromInteger arg :: a Source #

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

Methods

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

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

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

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

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

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

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply FromIntegerSym0 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 (+@#@$) t1) t2) Source #

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

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

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

sAbs :: forall (t :: Min a). Sing t -> Sing (Apply AbsSym0 t) Source #

sSignum :: forall (t :: Min a). Sing t -> Sing (Apply SignumSym0 t) Source #

sFromInteger :: forall (t :: Natural). Sing t -> Sing (Apply FromIntegerSym0 t) Source #

PShow (First a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow (Last a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow (Max a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow (Min a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow (WrappedMonoid m) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow (Dual a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow (Product a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow (Sum a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

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 t1) t2) t3) Source #

sShow_ :: forall (t :: First a). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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 t1) t2) t3) Source #

sShow_ :: forall (t :: Last a). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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 t1) t2) t3) Source #

sShow_ :: forall (t :: Max a). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [Max a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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 t1) t2) t3) Source #

sShow_ :: forall (t :: Min a). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [Min a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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 t1) t2) t3) Source #

sShow_ :: forall (t :: WrappedMonoid m). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [WrappedMonoid m]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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 t1) t2) t3) Source #

sShow_ :: forall (t :: Dual a). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [Dual a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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 t1) t2) t3) Source #

sShow_ :: forall (t :: Product a). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [Product a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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 t1) t2) t3) Source #

sShow_ :: forall (t :: Sum a). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [Sum a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 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

Methods

showsPrec :: Int -> SWrappedMonoid z -> ShowS

show :: SWrappedMonoid z -> String

showList :: [SWrappedMonoid z] -> ShowS

(SingKind a, SingKind b) => SingKind (Arg a b) Source # 
Instance details

Associated Types

type Demote (Arg a b) = (r :: Type) #

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

Associated Types

type arg == arg1 :: Bool Source #

type arg /= arg1 :: Bool Source #

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 (==@#@$) t1) t2) Source #

(%/=) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (/=@#@$) t1) t2) Source #

POrd (Arg a b) Source # 
Instance details

Associated Types

type Compare arg arg1 :: Ordering Source #

type arg < arg1 :: Bool Source #

type arg <= arg1 :: Bool Source #

type arg > arg1 :: Bool Source #

type arg >= arg1 :: Bool Source #

type Max arg arg1 :: a Source #

type Min arg arg1 :: a Source #

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 t1) t2) Source #

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

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

(%>) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) Source #

(%>=) :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) Source #

sMax :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) Source #

sMin :: forall (t1 :: Arg a b) (t2 :: Arg a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) Source #

PShow (Arg a b) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

(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 t1) t2) t3) Source #

sShow_ :: forall (t :: Arg a b). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t1 :: [Arg a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) Source #

(SingI n, SingI n) => SingI ('Arg n n :: Arg a b) Source # 
Instance details

Methods

sing :: Sing ('Arg n0 n) #