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

Data.Monoid.Singletons

Description

Defines the promoted version of Monoid, PMonoid, and the singleton version, SMonoid.

Synopsis

Documentation

class PMonoid a Source #

Associated Types

type Mempty :: a Source #

type Mappend (arg :: a) (arg :: a) :: a Source #

type Mappend a a = Apply (Apply Mappend_6989586621680336638Sym0 a) a

type Mconcat (arg :: [a]) :: a Source #

type Mconcat a = Apply Mconcat_6989586621680336652Sym0 a

Instances

Instances details
PMonoid All Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid Any Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid Ordering Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid () Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid Symbol Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Down a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Dual a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Product a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Sum a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Maybe a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid [a] Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (a ~> b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (a, b) Source # 
Instance details

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

PMonoid (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Monoid.Singletons

Associated Types

type Mempty :: a Source #

type Mappend arg arg1 :: a Source #

type Mconcat arg :: a Source #

class SSemigroup a => SMonoid a where Source #

Minimal complete definition

sMempty

Methods

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

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

default sMappend :: forall (t :: a) (t :: a). (Apply (Apply MappendSym0 t) t :: a) ~ Apply (Apply Mappend_6989586621680336638Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply MappendSym0 t) t :: a) Source #

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

default sMconcat :: forall (t :: [a]). (Apply MconcatSym0 t :: a) ~ Apply Mconcat_6989586621680336652Sym0 t => Sing t -> Sing (Apply MconcatSym0 t :: a) Source #

Instances

Instances details
SMonoid All Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid Any Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid Ordering Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid () Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid Symbol Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Functor.Identity.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Semigroup.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Semigroup.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Semigroup.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid [a] Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Functor.Const.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

sMappend :: forall (t1 :: (a, b, c, d)) (t2 :: (a, b, c, d)). Sing t1 -> Sing t2 -> Sing (Apply (Apply MappendSym0 t1) t2) Source #

sMconcat :: forall (t :: [(a, b, c, d)]). Sing t -> Sing (Apply MconcatSym0 t) Source #

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

Defined in Data.Monoid.Singletons

Methods

sMempty :: Sing MemptySym0 Source #

sMappend :: forall (t1 :: (a, b, c, d, e)) (t2 :: (a, b, c, d, e)). Sing t1 -> Sing t2 -> Sing (Apply (Apply MappendSym0 t1) t2) Source #

sMconcat :: forall (t :: [(a, b, c, d, e)]). Sing t -> Sing (Apply MconcatSym0 t) Source #

type family Sing :: k -> Type #

Instances

Instances details
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SAll
type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

type Sing = SAny
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SVoid
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing Source # 
Instance details

Defined in Data.Singletons.Base.TypeError

type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SNat
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = STuple0
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

type Sing = SBool
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SChar
type Sing Source # 
Instance details

Defined in GHC.TypeLits.Singletons.Internal

type Sing = SSymbol
type Sing Source # 
Instance details

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Ord.Singletons

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

type Sing Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Singletons.Base.Instances

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

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

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

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

Instance details

Defined in Data.Singletons.Base.TypeRepTYPE

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Proxy.Singletons

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

Defined in Data.Semigroup.Singletons

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

Defined in Data.Singletons

type Sing = SWrappedSing :: WrappedSing a -> Type
type Sing 
Instance details

Defined in Data.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Functor.Const.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Functor.Product.Singletons

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

Defined in Data.Functor.Sum.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Functor.Compose.Singletons

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Singletons.Base.Instances

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

Defined in Data.Singletons.Base.Instances

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

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

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

Methods

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

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

Defined in Data.Semigroup.Singletons.Internal

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

Methods

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

show :: SDual z -> String #

showList :: [SDual z] -> ShowS #

data SAll :: All -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

Methods

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

SDecide Bool => TestEquality SAll Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Methods

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

show :: SAll z -> String #

showList :: [SAll z] -> ShowS #

data SAny :: Any -> Type where Source #

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

Methods

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

SDecide Bool => TestEquality SAny Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Methods

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

show :: SAny z -> String #

showList :: [SAny z] -> ShowS #

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

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

Methods

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

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

Defined in Data.Semigroup.Singletons.Internal

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

Methods

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

show :: SSum z -> String #

showList :: [SSum z] -> ShowS #

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

Constructors

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

Methods

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

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

Defined in Data.Semigroup.Singletons.Internal

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

Methods

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

show :: SProduct z -> String #

showList :: [SProduct z] -> ShowS #

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

Constructors

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

Instances

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

Defined in Data.Monoid.Singletons

Methods

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

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

Defined in Data.Monoid.Singletons

Methods

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

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

Defined in Data.Monoid.Singletons

Methods

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

show :: SFirst z -> String #

showList :: [SFirst z] -> ShowS #

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

Constructors

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

Instances

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

Defined in Data.Monoid.Singletons

Methods

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

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

Defined in Data.Monoid.Singletons

Methods

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

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

Defined in Data.Monoid.Singletons

Methods

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

show :: SLast z -> String #

showList :: [SLast z] -> ShowS #

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 GetFirst (a :: First (a :: Type)) :: Maybe a where ... Source #

Equations

GetFirst ('First field) = field 

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

Equations

GetLast ('Last field) = field 

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

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

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

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

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

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

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

Defunctionalization symbols

type family MemptySym0 :: a where ... Source #

Equations

MemptySym0 = Mempty 

data MappendSym0 :: (~>) a ((~>) a a) Source #

Instances

Instances details
SMonoid a => SingI (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

SuppressUnusedWarnings (MappendSym0 :: TyFun a (a ~> a) -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621680336631 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym0 :: TyFun a (a ~> a) -> Type) (a6989586621680336631 :: a) = MappendSym1 a6989586621680336631

data MappendSym1 (a6989586621680336631 :: a) :: (~>) a a Source #

Instances

Instances details
SMonoid a => SingI1 (MappendSym1 :: a -> TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

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

(SMonoid a, SingI d) => SingI (MappendSym1 d :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

Methods

sing :: Sing (MappendSym1 d)

SuppressUnusedWarnings (MappendSym1 a6989586621680336631 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym1 a6989586621680336631 :: TyFun a a -> Type) (a6989586621680336632 :: a) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MappendSym1 a6989586621680336631 :: TyFun a a -> Type) (a6989586621680336632 :: a) = Mappend a6989586621680336631 a6989586621680336632

type family MappendSym2 (a6989586621680336631 :: a) (a6989586621680336632 :: a) :: a where ... Source #

Equations

MappendSym2 a6989586621680336631 a6989586621680336632 = Mappend a6989586621680336631 a6989586621680336632 

data MconcatSym0 :: (~>) [a] a Source #

Instances

Instances details
SMonoid a => SingI (MconcatSym0 :: TyFun [a] a -> Type) Source # 
Instance details

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621680336635 :: [a]) Source # 
Instance details

Defined in Data.Monoid.Singletons

type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621680336635 :: [a]) = Mconcat a6989586621680336635

type family MconcatSym1 (a6989586621680336635 :: [a]) :: a where ... Source #

Equations

MconcatSym1 a6989586621680336635 = Mconcat a6989586621680336635 

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing DualSym0

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

DualSym1 a6989586621679703748 = 'Dual a6989586621679703748 

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

GetDualSym1 a6989586621679703751 = GetDual a6989586621679703751 

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

Instances

Instances details
SingI AllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing AllSym0

SuppressUnusedWarnings AllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

AllSym1 a6989586621679703765 = 'All a6989586621679703765 

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

Instances

Instances details
SingI GetAllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing GetAllSym0

SuppressUnusedWarnings GetAllSym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

GetAllSym1 a6989586621679703768 = GetAll a6989586621679703768 

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

Instances

Instances details
SingI AnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing AnySym0

SuppressUnusedWarnings AnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

AnySym1 a6989586621679703781 = 'Any a6989586621679703781 

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

Instances

Instances details
SingI GetAnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing GetAnySym0

SuppressUnusedWarnings GetAnySym0 Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

GetAnySym1 a6989586621679703784 = GetAny a6989586621679703784 

data SumSym0 :: (~>) a (Sum (a :: Type)) Source #

Instances

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

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing SumSym0

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

SumSym1 a6989586621679703800 = 'Sum a6989586621679703800 

data GetSumSym0 :: (~>) (Sum (a :: Type)) a Source #

Instances

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

Defined in Data.Semigroup.Singletons.Internal

Methods

sing :: Sing GetSumSym0

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

GetSumSym1 a6989586621679703803 = GetSum a6989586621679703803 

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

ProductSym1 a6989586621679703819 = 'Product a6989586621679703819 

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

Instances

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

Defined in Data.Semigroup.Singletons.Internal

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

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

Equations

GetProductSym1 a6989586621679703822 = GetProduct a6989586621679703822 

data FirstSym0 :: (~>) (Maybe a) (First (a :: Type)) Source #

Instances

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

Defined in Data.Monoid.Singletons

Methods

sing :: Sing FirstSym0

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

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

Equations

FirstSym1 a6989586621680341560 = 'First a6989586621680341560 

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

Instances

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

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

Equations

GetFirstSym1 a6989586621680341563 = GetFirst a6989586621680341563 

data LastSym0 :: (~>) (Maybe a) (Last (a :: Type)) Source #

Instances

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

Defined in Data.Monoid.Singletons

Methods

sing :: Sing LastSym0

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

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

Equations

LastSym1 a6989586621680341584 = 'Last a6989586621680341584 

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

Instances

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

Defined in Data.Monoid.Singletons

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

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

Equations

GetLastSym1 a6989586621680341587 = GetLast a6989586621680341587 

Orphan instances

PApplicative First Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg1 arg2 :: f c Source #

type arg *> arg1 :: f b Source #

type arg <* arg1 :: f a Source #

PApplicative Last Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg1 arg2 :: f c Source #

type arg *> arg1 :: f b Source #

type arg <* arg1 :: f a Source #

PFunctor First Source # 
Instance details

Associated Types

type Fmap arg arg1 :: f b Source #

type arg <$ arg1 :: f a Source #

PFunctor Last Source # 
Instance details

Associated Types

type Fmap arg arg1 :: f b Source #

type arg <$ arg1 :: f a Source #

PMonad First Source # 
Instance details

Associated Types

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

type arg >> arg1 :: m b Source #

type Return arg :: m a Source #

PMonad Last Source # 
Instance details

Associated Types

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

type arg >> arg1 :: m b Source #

type Return arg :: m a Source #

SApplicative First Source # 
Instance details

Methods

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

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

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

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

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

SApplicative Last Source # 
Instance details

Methods

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

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

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

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

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

SFunctor First Source # 
Instance details

Methods

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

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

SFunctor Last Source # 
Instance details

Methods

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

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

SMonad First Source # 
Instance details

Methods

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

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

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

SMonad Last Source # 
Instance details

Methods

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

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

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

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

Associated Types

type Demote (First a) = (r :: Type)

Methods

fromSing :: forall (a0 :: First a). Sing a0 -> Demote (First a)

toSing :: Demote (First a) -> SomeSing (First a)

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

Associated Types

type Demote (Last a) = (r :: Type)

Methods

fromSing :: forall (a0 :: Last a). Sing a0 -> Demote (Last a)

toSing :: Demote (Last a) -> SomeSing (Last a)

SDecide (Maybe a) => SDecide (First a) Source # 
Instance details

Methods

(%~) :: forall (a0 :: First a) (b :: First a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SDecide (Maybe a) => SDecide (Last a) Source # 
Instance details

Methods

(%~) :: forall (a0 :: Last a) (b :: Last a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

PEq (First a) Source # 
Instance details

Associated Types

type arg == arg1 :: Bool Source #

type arg /= arg1 :: Bool Source #

PEq (Last a) Source # 
Instance details

Associated Types

type arg == arg1 :: Bool Source #

type arg /= arg1 :: Bool Source #

SEq (Maybe a) => SEq (First a) Source # 
Instance details

Methods

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

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

SEq (Maybe a) => SEq (Last a) Source # 
Instance details

Methods

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

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

POrd (First a) Source # 
Instance details

Associated Types

type Compare arg arg1 :: Ordering Source #

type arg < arg1 :: Bool Source #

type arg <= arg1 :: Bool Source #

type arg > arg1 :: Bool Source #

type arg >= arg1 :: Bool Source #

type Max arg arg1 :: a Source #

type Min arg arg1 :: a Source #

POrd (Last a) Source # 
Instance details

Associated Types

type Compare arg arg1 :: Ordering Source #

type arg < arg1 :: Bool Source #

type arg <= arg1 :: Bool Source #

type arg > arg1 :: Bool Source #

type arg >= arg1 :: Bool Source #

type Max arg arg1 :: a Source #

type Min arg arg1 :: a Source #

SOrd (Maybe a) => SOrd (First a) Source # 
Instance details

Methods

sCompare :: forall (t1 :: First a) (t2 :: First a). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) Source #

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

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

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

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

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

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

SOrd (Maybe a) => SOrd (Last a) Source # 
Instance details

Methods

sCompare :: forall (t1 :: Last a) (t2 :: Last a). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) Source #

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

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

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

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

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

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

PSemigroup (First a) Source # 
Instance details

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Associated Types

type arg <> arg1 :: a Source #

type Sconcat arg :: a Source #

SSemigroup (First a) Source # 
Instance details

Methods

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

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

SSemigroup (Last a) Source # 
Instance details

Methods

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

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

PShow (First a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

PShow (Last a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg1 :: Symbol Source #

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

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: First a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) Source #

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

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

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

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Last a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) Source #

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

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

SingI1 ('First :: Maybe a -> First a) Source # 
Instance details

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('First x)

SingI1 ('Last :: Maybe a -> Last a) Source # 
Instance details

Methods

liftSing :: forall (x :: k1). Sing x -> Sing ('Last x)

SingI n => SingI ('First n :: First a) Source # 
Instance details

Methods

sing :: Sing ('First n)

SingI n => SingI ('Last n :: Last a) Source # 
Instance details

Methods

sing :: Sing ('Last n)