singletons-2.6: A framework for generating singleton types
Copyright(C) 2018 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.Semigroup

Description

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

Synopsis

Documentation

class PSemigroup (a :: Type) Source #

Associated Types

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

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

type Sconcat a = Apply Sconcat_6989586621679840854Sym0 a Source #

Instances

Instances details
PSemigroup Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup () Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup All Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (WrappedMonoid m) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Identity a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Dual a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Sum a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Product a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Down a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (a, b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Const a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: 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) infixr 6 Source #

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

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

Instances

Instances details
SSemigroup Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: Ordering) (t :: Ordering). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

SSemigroup Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

SSemigroup () Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: Void) (t :: Void). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

SSemigroup All Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: All) (t :: All). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

SSemigroup Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: Any) (t :: Any). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

SSemigroup [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: [a]) (t :: [a]). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

SSemigroup (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

SSemigroup (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

(%<>) :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

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

Defined in Data.Singletons.Prelude.Identity

Methods

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

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

SSemigroup (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

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

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

SSemigroup (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup (Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: Either a b) (t :: Either a b). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: (a, b)) (t :: (a, b)). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: a ~> b) (t :: a ~> b). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

sSconcat :: forall (t :: NonEmpty (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.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: (a, b, c)) (t :: (a, b, c)). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

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

Defined in Data.Singletons.Prelude.Const

Methods

(%<>) :: forall (t :: Const a b) (t :: Const a b). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

sSconcat :: forall (t :: NonEmpty (Const a b)). 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.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) 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.Singletons.Prelude.Semigroup.Internal

Methods

(%<>) :: forall (t :: (a, b, c, d, e)) (t :: (a, b, c, d, e)). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

type family Sing :: k -> Type Source #

The singleton kind-indexed type family.

Instances

Instances details
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SBool
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

type Sing = SSymbol
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = STuple0
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.TypeError

type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.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.TypeRepTYPE

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Sing = SOption :: Option a -> Type
type Sing Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Ord

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Internal

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

Defined in Data.Singletons.Internal

type Sing Source # 
Instance details

Defined in Data.Singletons.Sigma

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Const

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

Defined in Data.Singletons.Prelude.Instances

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

data SMin :: forall a. Min a -> Type where Source #

Constructors

SMin 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SMin z -> String #

showList :: [SMin z] -> ShowS #

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

Constructors

SMax 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SMax z -> String #

showList :: [SMax z] -> ShowS #

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

Constructors

SFirst 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SFirst z -> String #

showList :: [SFirst z] -> ShowS #

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

Constructors

SLast 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SLast z -> String #

showList :: [SLast z] -> ShowS #

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

Constructors

SWrapMonoid 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

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

Constructors

SDual 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SDual z -> String #

showList :: [SDual z] -> ShowS #

data SAll :: All -> Type where Source #

Constructors

SAll 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SAll z -> String #

showList :: [SAll z] -> ShowS #

data SAny :: Any -> Type where Source #

Constructors

SAny 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SAny z -> String #

showList :: [SAny z] -> ShowS #

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

Constructors

SSum 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SSum z -> String #

showList :: [SSum z] -> ShowS #

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

Constructors

SProduct 

Fields

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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.Singletons.Prelude.Semigroup.Internal

Methods

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SProduct z -> String #

showList :: [SProduct z] -> ShowS #

data SOption :: forall a. Option a -> Type where Source #

Constructors

SOption 

Fields

Instances

Instances details
SDecide (Maybe a) => TestCoercion (SOption :: Option a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

testCoercion :: forall (a0 :: k) (b :: k). SOption a0 -> SOption b -> Maybe (Coercion a0 b) #

SDecide (Maybe a) => TestEquality (SOption :: Option a -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

testEquality :: forall (a0 :: k) (b :: k). SOption a0 -> SOption b -> Maybe (a0 :~: b) #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: SOption z -> String #

showList :: [SOption z] -> ShowS #

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

Constructors

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

Instances

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

Defined in Data.Singletons.Prelude.Semigroup

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 

type family GetOption (a :: Option (a :: Type)) :: Maybe a where ... Source #

Equations

GetOption ('Option field) = field 

option_ :: b -> (a -> b) -> Option a -> b Source #

sOption_ :: forall b a (t :: b) (t :: (~>) a b) (t :: Option a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply Option_Sym0 t) t) t :: b) Source #

type family Option_ (a :: b) (a :: (~>) a b) (a :: Option a) :: b where ... Source #

Equations

Option_ n j ('Option m) = Apply (Apply (Apply Maybe_Sym0 n) j) m 

Defunctionalization symbols

data (<>@#@$) :: forall a6989586621679840612. (~>) a6989586621679840612 ((~>) a6989586621679840612 a6989586621679840612) infixr 6 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply ((<>@#@$) :: TyFun a6989586621679840612 (a6989586621679840612 ~> a6989586621679840612) -> Type) (arg6989586621679840847 :: a6989586621679840612) = (<>@#@$$) arg6989586621679840847

data (<>@#@$$) (arg6989586621679840847 :: a6989586621679840612) :: (~>) a6989586621679840612 a6989586621679840612 infixr 6 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

SuppressUnusedWarnings ((<>@#@$$) arg6989586621679840847 :: TyFun a6989586621679840612 a6989586621679840612 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply ((<>@#@$$) arg6989586621679840847 :: TyFun a a -> Type) (arg6989586621679840848 :: a) = arg6989586621679840847 <> arg6989586621679840848

type (<>@#@$$$) (arg6989586621679840847 :: a6989586621679840612) (arg6989586621679840848 :: a6989586621679840612) = (<>) arg6989586621679840847 arg6989586621679840848 Source #

data SconcatSym0 :: forall a6989586621679840612. (~>) (NonEmpty a6989586621679840612) a6989586621679840612 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type SconcatSym1 (arg6989586621679840851 :: NonEmpty a6989586621679840612) = Sconcat arg6989586621679840851 Source #

data MinSym0 :: forall (a6989586621679069715 :: Type). (~>) a6989586621679069715 (Min (a6989586621679069715 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type MinSym1 (t6989586621679850232 :: a6989586621679069715) = 'Min t6989586621679850232 Source #

data GetMinSym0 :: forall (a6989586621679069715 :: Type). (~>) (Min (a6989586621679069715 :: Type)) a6989586621679069715 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetMinSym1 (a6989586621679850229 :: Min (a6989586621679069715 :: Type)) = GetMin a6989586621679850229 Source #

data MaxSym0 :: forall (a6989586621679069719 :: Type). (~>) a6989586621679069719 (Max (a6989586621679069719 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type MaxSym1 (t6989586621679850251 :: a6989586621679069719) = 'Max t6989586621679850251 Source #

data GetMaxSym0 :: forall (a6989586621679069719 :: Type). (~>) (Max (a6989586621679069719 :: Type)) a6989586621679069719 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetMaxSym1 (a6989586621679850248 :: Max (a6989586621679069719 :: Type)) = GetMax a6989586621679850248 Source #

data FirstSym0 :: forall (a6989586621679069727 :: Type). (~>) a6989586621679069727 (First (a6989586621679069727 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type FirstSym1 (t6989586621679850270 :: a6989586621679069727) = 'First t6989586621679850270 Source #

data GetFirstSym0 :: forall (a6989586621679069727 :: Type). (~>) (First (a6989586621679069727 :: Type)) a6989586621679069727 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetFirstSym1 (a6989586621679850267 :: First (a6989586621679069727 :: Type)) = GetFirst a6989586621679850267 Source #

data LastSym0 :: forall (a6989586621679069723 :: Type). (~>) a6989586621679069723 (Last (a6989586621679069723 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type LastSym1 (t6989586621679850289 :: a6989586621679069723) = 'Last t6989586621679850289 Source #

data GetLastSym0 :: forall (a6989586621679069723 :: Type). (~>) (Last (a6989586621679069723 :: Type)) a6989586621679069723 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetLastSym1 (a6989586621679850286 :: Last (a6989586621679069723 :: Type)) = GetLast a6989586621679850286 Source #

data WrapMonoidSym0 :: forall (m6989586621679093626 :: Type). (~>) m6989586621679093626 (WrappedMonoid (m6989586621679093626 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type WrapMonoidSym1 (t6989586621679850308 :: m6989586621679093626) = 'WrapMonoid t6989586621679850308 Source #

data UnwrapMonoidSym0 :: forall (m6989586621679093626 :: Type). (~>) (WrappedMonoid (m6989586621679093626 :: Type)) m6989586621679093626 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type UnwrapMonoidSym1 (a6989586621679850305 :: WrappedMonoid (m6989586621679093626 :: Type)) = UnwrapMonoid a6989586621679850305 Source #

data DualSym0 :: forall (a6989586621679091700 :: Type). (~>) a6989586621679091700 (Dual (a6989586621679091700 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type DualSym1 (t6989586621679850147 :: a6989586621679091700) = 'Dual t6989586621679850147 Source #

data GetDualSym0 :: forall (a6989586621679091700 :: Type). (~>) (Dual (a6989586621679091700 :: Type)) a6989586621679091700 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetDualSym1 (a6989586621679850144 :: Dual (a6989586621679091700 :: Type)) = GetDual a6989586621679850144 Source #

data AllSym0 :: (~>) Bool All Source #

Instances

Instances details
SingI AllSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings AllSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type AllSym1 (t6989586621679850161 :: Bool) = 'All t6989586621679850161 Source #

data GetAllSym0 :: (~>) All Bool Source #

Instances

Instances details
SuppressUnusedWarnings GetAllSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetAllSym1 (a6989586621679850158 :: All) = GetAll a6989586621679850158 Source #

data AnySym0 :: (~>) Bool Any Source #

Instances

Instances details
SingI AnySym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings AnySym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type AnySym1 (t6989586621679850175 :: Bool) = 'Any t6989586621679850175 Source #

data GetAnySym0 :: (~>) Any Bool Source #

Instances

Instances details
SuppressUnusedWarnings GetAnySym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetAnySym1 (a6989586621679850172 :: Any) = GetAny a6989586621679850172 Source #

data SumSym0 :: forall (a6989586621679091685 :: Type). (~>) a6989586621679091685 (Sum (a6989586621679091685 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type SumSym1 (t6989586621679850194 :: a6989586621679091685) = 'Sum t6989586621679850194 Source #

data GetSumSym0 :: forall (a6989586621679091685 :: Type). (~>) (Sum (a6989586621679091685 :: Type)) a6989586621679091685 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetSumSym1 (a6989586621679850191 :: Sum (a6989586621679091685 :: Type)) = GetSum a6989586621679850191 Source #

data ProductSym0 :: forall (a6989586621679091690 :: Type). (~>) a6989586621679091690 (Product (a6989586621679091690 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type ProductSym1 (t6989586621679850213 :: a6989586621679091690) = 'Product t6989586621679850213 Source #

data GetProductSym0 :: forall (a6989586621679091690 :: Type). (~>) (Product (a6989586621679091690 :: Type)) a6989586621679091690 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetProductSym1 (a6989586621679850210 :: Product (a6989586621679091690 :: Type)) = GetProduct a6989586621679850210 Source #

data OptionSym0 :: forall (a6989586621679069711 :: Type). (~>) (Maybe a6989586621679069711) (Option (a6989586621679069711 :: Type)) Source #

Instances

Instances details
SingI (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings (OptionSym0 :: TyFun (Maybe a6989586621679069711) (Option a6989586621679069711) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621679850128 :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (OptionSym0 :: TyFun (Maybe a) (Option a) -> Type) (t6989586621679850128 :: Maybe a) = 'Option t6989586621679850128

type OptionSym1 (t6989586621679850128 :: Maybe a6989586621679069711) = 'Option t6989586621679850128 Source #

data GetOptionSym0 :: forall (a6989586621679069711 :: Type). (~>) (Option (a6989586621679069711 :: Type)) (Maybe a6989586621679069711) Source #

Instances

Instances details
SuppressUnusedWarnings (GetOptionSym0 :: TyFun (Option a6989586621679069711) (Maybe a6989586621679069711) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679850125 :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (GetOptionSym0 :: TyFun (Option a) (Maybe a) -> Type) (a6989586621679850125 :: Option a) = GetOption a6989586621679850125

type GetOptionSym1 (a6989586621679850125 :: Option (a6989586621679069711 :: Type)) = GetOption a6989586621679850125 Source #

data ArgSym0 :: forall (a6989586621679070612 :: Type) (b6989586621679070613 :: Type). (~>) a6989586621679070612 ((~>) b6989586621679070613 (Arg (a6989586621679070612 :: Type) (b6989586621679070613 :: Type))) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup

SuppressUnusedWarnings (ArgSym0 :: TyFun a6989586621679070612 (b6989586621679070613 ~> Arg a6989586621679070612 b6989586621679070613) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (ArgSym0 :: TyFun a6989586621679070612 (b6989586621679070613 ~> Arg a6989586621679070612 b6989586621679070613) -> Type) (t6989586621680915597 :: a6989586621679070612) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (ArgSym0 :: TyFun a6989586621679070612 (b6989586621679070613 ~> Arg a6989586621679070612 b6989586621679070613) -> Type) (t6989586621680915597 :: a6989586621679070612) = ArgSym1 t6989586621680915597 b6989586621679070613 :: TyFun b6989586621679070613 (Arg a6989586621679070612 b6989586621679070613) -> Type

data ArgSym1 (t6989586621680915597 :: a6989586621679070612 :: Type) :: forall (b6989586621679070613 :: Type). (~>) b6989586621679070613 (Arg (a6989586621679070612 :: Type) (b6989586621679070613 :: Type)) Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sing :: Sing (ArgSym1 d b) Source #

SuppressUnusedWarnings (ArgSym1 t6989586621680915597 b6989586621679070613 :: TyFun b6989586621679070613 (Arg a6989586621679070612 b6989586621679070613) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

type Apply (ArgSym1 t6989586621680915597 b :: TyFun b (Arg a b) -> Type) (t6989586621680915598 :: b) = 'Arg t6989586621680915597 t6989586621680915598

type ArgSym2 (t6989586621680915597 :: a6989586621679070612) (t6989586621680915598 :: b6989586621679070613) = 'Arg t6989586621680915597 t6989586621680915598 Source #

Orphan instances

SMonadPlus Option Source # 
Instance details

Methods

sMzero :: Sing MzeroSym0 Source #

sMplus :: forall a (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply MplusSym0 t) t) Source #

SAlternative Option Source # 
Instance details

Methods

sEmpty :: Sing EmptySym0 Source #

(%<|>) :: forall a (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply (<|>@#@$) t) t) Source #

SMonad Min Source # 
Instance details

Methods

(%>>=) :: forall a b (t :: Min a) (t :: a ~> Min b). Sing t -> Sing t -> Sing (Apply (Apply (>>=@#@$) t) t) Source #

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

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

SMonad Max Source # 
Instance details

Methods

(%>>=) :: forall a b (t :: Max a) (t :: a ~> Max b). Sing t -> Sing t -> Sing (Apply (Apply (>>=@#@$) t) t) Source #

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

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

SMonad First Source # 
Instance details

Methods

(%>>=) :: forall a b (t :: First a) (t :: a ~> First b). Sing t -> Sing t -> Sing (Apply (Apply (>>=@#@$) t) t) Source #

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

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

SMonad Last Source # 
Instance details

Methods

(%>>=) :: forall a b (t :: Last a) (t :: a ~> Last b). Sing t -> Sing t -> Sing (Apply (Apply (>>=@#@$) t) t) Source #

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

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

SMonad Option Source # 
Instance details

Methods

(%>>=) :: forall a b (t :: Option a) (t :: a ~> Option b). Sing t -> Sing t -> Sing (Apply (Apply (>>=@#@$) t) t) Source #

(%>>) :: forall a b (t :: Option a) (t :: Option b). Sing t -> Sing t -> Sing (Apply (Apply (>>@#@$) t) t) Source #

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

SApplicative Min Source # 
Instance details

Methods

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

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

sLiftA2 :: forall a b c (t :: a ~> (b ~> c)) (t :: Min a) (t :: Min b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

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

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

SApplicative Max Source # 
Instance details

Methods

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

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

sLiftA2 :: forall a b c (t :: a ~> (b ~> c)) (t :: Max a) (t :: Max b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

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

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

SApplicative First Source # 
Instance details

Methods

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

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

sLiftA2 :: forall a b c (t :: a ~> (b ~> c)) (t :: First a) (t :: First b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

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

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

SApplicative Last Source # 
Instance details

Methods

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

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

sLiftA2 :: forall a b c (t :: a ~> (b ~> c)) (t :: Last a) (t :: Last b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

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

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

SApplicative Option Source # 
Instance details

Methods

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

(%<*>) :: forall a b (t :: Option (a ~> b)) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply (<*>@#@$) t) t) Source #

sLiftA2 :: forall a b c (t :: a ~> (b ~> c)) (t :: Option a) (t :: Option b). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

(%*>) :: forall a b (t :: Option a) (t :: Option b). Sing t -> Sing t -> Sing (Apply (Apply (*>@#@$) t) t) Source #

(%<*) :: forall a b (t :: Option a) (t :: Option b). Sing t -> Sing t -> Sing (Apply (Apply (<*@#@$) t) t) Source #

SFunctor Min Source # 
Instance details

Methods

sFmap :: forall a b (t :: a ~> b) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

SFunctor Max Source # 
Instance details

Methods

sFmap :: forall a b (t :: a ~> b) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

SFunctor First Source # 
Instance details

Methods

sFmap :: forall a b (t :: a ~> b) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

SFunctor Last Source # 
Instance details

Methods

sFmap :: forall a b (t :: a ~> b) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

SFunctor Option Source # 
Instance details

Methods

sFmap :: forall a b (t :: a ~> b) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

(%<$) :: forall a b (t :: a) (t :: Option b). Sing t -> Sing t -> Sing (Apply (Apply (<$@#@$) t) t) Source #

PMonadPlus Option Source # 
Instance details

Associated Types

type Mzero :: m a Source #

type Mplus arg arg :: m a Source #

PAlternative Option Source # 
Instance details

Associated Types

type Empty :: f a Source #

type arg <|> arg :: f a Source #

PMonad Min Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

PMonad Max Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

PMonad First Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

PMonad Last Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

PMonad Option Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

PApplicative Min Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative Max Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative First Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative Last Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative Option Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PFunctor Min Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor Max Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor First Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor Last Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor Option Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

SShow Bool => SShow All Source # 
Instance details

Methods

sShowsPrec :: forall (t :: Nat) (t :: All) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [All]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow Bool => SShow Any Source # 
Instance details

Methods

sShowsPrec :: forall (t :: Nat) (t :: Any) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

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

PShow All Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Any Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

SFoldable Min Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Max Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable First Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Last Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

SFoldable Option Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

PFoldable Min Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: 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 arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable First Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: 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 arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Option Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

STraversable Min Source # 
Instance details

Methods

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

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

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

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

STraversable Max Source # 
Instance details

Methods

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

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

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

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

STraversable First Source # 
Instance details

Methods

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

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

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

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

STraversable Last Source # 
Instance details

Methods

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

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

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

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

STraversable Option Source # 
Instance details

Methods

sTraverse :: forall a (f :: Type -> Type) b (t :: a ~> f b) (t :: Option a). SApplicative f => Sing t -> Sing t -> Sing (Apply (Apply TraverseSym0 t) t) Source #

sSequenceA :: forall (f :: Type -> Type) a (t :: Option (f a)). SApplicative f => Sing t -> Sing (Apply SequenceASym0 t) Source #

sMapM :: forall a (m :: Type -> Type) b (t :: a ~> m b) (t :: Option a). SMonad m => Sing t -> Sing t -> Sing (Apply (Apply MapMSym0 t) t) Source #

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

PTraversable Min Source # 
Instance details

Associated Types

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

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

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

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

PTraversable Max Source # 
Instance details

Associated Types

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

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

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

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

PTraversable First Source # 
Instance details

Associated Types

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

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

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

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

PTraversable Last Source # 
Instance details

Associated Types

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

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

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

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

PTraversable Option Source # 
Instance details

Associated Types

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

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

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

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

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

Methods

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

show :: SAny z -> String #

showList :: [SAny z] -> ShowS #

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

Methods

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

show :: SAll z -> String #

showList :: [SAll z] -> ShowS #

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

Methods

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

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

(%*) :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply (*@#@$) t) t) 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 :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t) Source #

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

Methods

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

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

(%*) :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply (*@#@$) t) t) 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 :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t) Source #

PNum (Min a) Source # 
Instance details

Associated Types

type arg + arg :: a Source #

type arg - arg :: a Source #

type arg * arg :: a Source #

type Negate arg :: a Source #

type Abs arg :: a Source #

type Signum arg :: a Source #

type FromInteger arg :: a Source #

PNum (Max a) Source # 
Instance details

Associated Types

type arg + arg :: a Source #

type arg - arg :: a Source #

type arg * arg :: a Source #

type Negate arg :: a Source #

type Abs arg :: a Source #

type Signum arg :: a Source #

type FromInteger arg :: a Source #

SFunctor (Arg a) Source # 
Instance details

Methods

sFmap :: forall a0 b (t :: a0 ~> b) (t :: Arg a a0). Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

PFunctor (Arg a) Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a 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 :: Nat). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing (Apply (Apply EnumFromToSym0 t) t) Source #

sEnumFromThenTo :: forall (t :: Min a) (t :: Min a) (t :: Min a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t) t) t) 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 :: Nat). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing (Apply (Apply EnumFromToSym0 t) t) Source #

sEnumFromThenTo :: forall (t :: Max a) (t :: Max a) (t :: Max a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t) t) t) 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 :: Nat). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t :: First a) (t :: First a). Sing t -> Sing t -> Sing (Apply (Apply EnumFromToSym0 t) t) Source #

sEnumFromThenTo :: forall (t :: First a) (t :: First a) (t :: First a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t) t) t) 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 :: Nat). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing (Apply (Apply EnumFromToSym0 t) t) Source #

sEnumFromThenTo :: forall (t :: Last a) (t :: Last a) (t :: Last a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t) t) t) 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 :: Nat). Sing t -> Sing (Apply ToEnumSym0 t) Source #

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

sEnumFromTo :: forall (t :: WrappedMonoid a) (t :: WrappedMonoid a). Sing t -> Sing t -> Sing (Apply (Apply EnumFromToSym0 t) t) Source #

sEnumFromThenTo :: forall (t :: WrappedMonoid a) (t :: WrappedMonoid a) (t :: WrappedMonoid a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t) t) t) 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 :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

type EnumFromThenTo arg arg arg :: [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 :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

type EnumFromThenTo arg arg arg :: [a] 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 :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

type EnumFromThenTo arg arg arg :: [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 :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

type EnumFromThenTo arg arg arg :: [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 :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

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

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

Methods

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

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

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

Methods

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

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

SSemigroup (First a) Source # 
Instance details

Methods

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

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

SSemigroup (Last a) Source # 
Instance details

Methods

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

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

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

Methods

(%<>) :: forall (t :: WrappedMonoid m) (t :: WrappedMonoid m). Sing t -> Sing t -> Sing (Apply (Apply (<>@#@$) t) t) Source #

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

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

Methods

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

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

PSemigroup (Min a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Max a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (First a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (WrappedMonoid m) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Option a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

Methods

sShowsPrec :: forall (t :: Nat) (t :: Min a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Min a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Methods

sShowsPrec :: forall (t :: Nat) (t :: Max a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Max a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Methods

sShowsPrec :: forall (t :: Nat) (t :: First a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [First a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Methods

sShowsPrec :: forall (t :: Nat) (t :: Last a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Last a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Methods

sShowsPrec :: forall (t :: Nat) (t :: WrappedMonoid m) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [WrappedMonoid m]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow (Maybe a) => SShow (Option a) Source # 
Instance details

Methods

sShowsPrec :: forall (t :: Nat) (t :: Option a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Option a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Methods

sShowsPrec :: forall (t :: Nat) (t :: Dual a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Dual a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow a => SShow (Sum a) Source # 
Instance details

Methods

sShowsPrec :: forall (t :: Nat) (t :: Sum a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Sum a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow a => SShow (Product a) Source # 
Instance details

Methods

sShowsPrec :: forall (t :: Nat) (t :: Product a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Product a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

PShow (Min a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Max a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (First a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Last a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (WrappedMonoid m) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Option a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Dual a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Sum a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Product a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SSemigroup a => SMonoid (Option a) Source # 
Instance details

Methods

sMempty :: Sing MemptySym0 Source #

sMappend :: forall (t :: Option a) (t :: Option a). Sing t -> Sing t -> Sing (Apply (Apply MappendSym0 t) t) Source #

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

PMonoid (Min a) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Max a) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (WrappedMonoid m) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Option a) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

SFoldable (Arg a) Source # 
Instance details

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

PFoldable (Arg a) Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

STraversable (Arg a) Source # 
Instance details

Methods

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

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

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

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

PTraversable (Arg a) Source # 
Instance details

Associated Types

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

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

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

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

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

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 (SFirst z) Source # 
Instance details

Methods

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

show :: SFirst z -> String #

showList :: [SFirst 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 a => Show (SDual z) Source # 
Instance details

Methods

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

show :: SDual z -> String #

showList :: [SDual z] -> ShowS #

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

Methods

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

show :: SOption z -> String #

showList :: [SOption z] -> ShowS #

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

Associated Types

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

Methods

fromSing :: forall (a0 :: Arg a b). Sing a0 -> Demote (Arg a b) Source #

toSing :: Demote (Arg a b) -> SomeSing (Arg a b) Source #

PEq (Arg a b) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

SEq a => SEq (Arg a b) Source # 
Instance details

Methods

(%==) :: forall (a0 :: Arg a b) (b0 :: Arg a b). Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: forall (a0 :: Arg a b) (b0 :: Arg a b). Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

SOrd a => SOrd (Arg a b) Source # 
Instance details

Methods

sCompare :: forall (t :: Arg a b) (t :: Arg a b). Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

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

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

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

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

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

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

POrd (Arg a b) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

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

Methods

sShowsPrec :: forall (t :: Nat) (t :: Arg a b) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

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

PShow (Arg a b) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

Methods

sing :: Sing ('Arg0 n1 n2) Source #