singletons-2.7: 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.Monoid

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_6989586621680347251Sym0 a) a

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

type Mconcat a = Apply Mconcat_6989586621680347265Sym0 a

Instances

Instances details
PMonoid Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid () Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid All Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (WrappedMonoid m) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Identity a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Dual a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Sum a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Product a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Down a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (a, b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Proxy s) Source # 
Instance details

Defined in Data.Singletons.Prelude.Proxy

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (a ~> b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Const a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: 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_6989586621680347251Sym0 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_6989586621680347265Sym0 t => Sing t -> Sing (Apply MconcatSym0 t :: a) Source #

Instances

Instances details
SMonoid Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid () Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid All Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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 #

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

Defined in Data.Singletons.Prelude.Identity

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

SMonoid (Proxy s) Source # 
Instance details

Defined in Data.Singletons.Prelude.Proxy

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

sMconcat :: forall (t :: [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.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

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

Defined in Data.Singletons.Prelude.Const

Methods

sMempty :: Sing MemptySym0 Source #

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

sMconcat :: forall (t :: [Const a b]). 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.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

sMappend :: forall (t :: (a, b, c, d)) (t :: (a, b, c, d)). Sing t -> Sing t -> Sing (Apply (Apply MappendSym0 t) t) 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.Singletons.Prelude.Monoid

Methods

sMempty :: Sing MemptySym0 Source #

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

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

type family Sing 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.Prelude.Proxy

type Sing = SProxy :: Proxy t -> 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 SDual z 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.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 z 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.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 z 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.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 z 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.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 z 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.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 SFirst z 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.Singletons.Prelude.Monoid

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.Singletons.Prelude.Monoid

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.Singletons.Prelude.Monoid

Methods

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

show :: SFirst z -> String #

showList :: [SFirst z] -> ShowS #

data SLast z 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.Singletons.Prelude.Monoid

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.Singletons.Prelude.Monoid

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.Singletons.Prelude.Monoid

Methods

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

show :: SLast z -> String #

showList :: [SLast z] -> ShowS #

type family GetDual a where ... Source #

Equations

GetDual ('Dual field) = field 

type family GetAll a where ... Source #

Equations

GetAll ('All field) = field 

type family GetAny a where ... Source #

Equations

GetAny ('Any field) = field 

type family GetSum a where ... Source #

Equations

GetSum ('Sum field) = field 

type family GetProduct a where ... Source #

Equations

GetProduct ('Product field) = field 

type family GetFirst a where ... Source #

Equations

GetFirst ('First field) = field 

type family GetLast 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

data MappendSym0 a6989586621680347244 Source #

Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

data MappendSym1 a6989586621680347244 a6989586621680347245 Source #

Instances

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sing :: Sing (MappendSym1 d) Source #

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

Defined in Data.Singletons.Prelude.Monoid

type Apply (MappendSym1 a6989586621680347244 :: TyFun a a -> Type) (a6989586621680347245 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (MappendSym1 a6989586621680347244 :: TyFun a a -> Type) (a6989586621680347245 :: a) = MappendSym2 a6989586621680347244 a6989586621680347245

type MappendSym2 (a6989586621680347244 :: a) (a6989586621680347245 :: a) = Mappend a6989586621680347244 a6989586621680347245 :: a Source #

data MconcatSym0 a6989586621680347248 Source #

Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

type Apply (MconcatSym0 :: TyFun [a] a -> Type) (a6989586621680347248 :: [a]) = MconcatSym1 a6989586621680347248

type MconcatSym1 (a6989586621680347248 :: [a]) = Mconcat a6989586621680347248 :: a Source #

data DualSym0 a6989586621679840113 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (DualSym0 :: TyFun a (Dual a) -> Type) (a6989586621679840113 :: a) = DualSym1 a6989586621679840113

type DualSym1 (a6989586621679840113 :: a) = 'Dual a6989586621679840113 :: Dual (a :: Type) Source #

data GetDualSym0 a6989586621679840116 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (GetDualSym0 :: TyFun (Dual a) a -> Type) (a6989586621679840116 :: Dual a) = GetDualSym1 a6989586621679840116

type GetDualSym1 (a6989586621679840116 :: Dual (a :: Type)) = GetDual a6989586621679840116 :: a Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AllSym0 (a6989586621679840130 :: Bool) = AllSym1 a6989586621679840130

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

data GetAllSym0 a6989586621679840133 Source #

Instances

Instances details
SingI GetAllSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings GetAllSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAllSym0 (a6989586621679840133 :: All) = GetAllSym1 a6989586621679840133

type GetAllSym1 (a6989586621679840133 :: All) = GetAll a6989586621679840133 :: Bool Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AnySym0 (a6989586621679840147 :: Bool) = AnySym1 a6989586621679840147

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

data GetAnySym0 a6989586621679840150 Source #

Instances

Instances details
SingI GetAnySym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

SuppressUnusedWarnings GetAnySym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply GetAnySym0 (a6989586621679840150 :: Any) = GetAnySym1 a6989586621679840150

type GetAnySym1 (a6989586621679840150 :: Any) = GetAny a6989586621679840150 :: Bool Source #

data SumSym0 a6989586621679840169 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (SumSym0 :: TyFun a (Sum a) -> Type) (a6989586621679840169 :: a) = SumSym1 a6989586621679840169

type SumSym1 (a6989586621679840169 :: a) = 'Sum a6989586621679840169 :: Sum (a :: Type) Source #

data GetSumSym0 a6989586621679840172 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (GetSumSym0 :: TyFun (Sum a) a -> Type) (a6989586621679840172 :: Sum a) = GetSumSym1 a6989586621679840172

type GetSumSym1 (a6989586621679840172 :: Sum (a :: Type)) = GetSum a6989586621679840172 :: a Source #

data ProductSym0 a6989586621679840191 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (ProductSym0 :: TyFun a (Product a) -> Type) (a6989586621679840191 :: a) = ProductSym1 a6989586621679840191

type ProductSym1 (a6989586621679840191 :: a) = 'Product a6989586621679840191 :: Product (a :: Type) Source #

data GetProductSym0 a6989586621679840194 Source #

Instances

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (GetProductSym0 :: TyFun (Product a) a -> Type) (a6989586621679840194 :: Product a) = GetProductSym1 a6989586621679840194

type GetProductSym1 (a6989586621679840194 :: Product (a :: Type)) = GetProduct a6989586621679840194 :: a Source #

data FirstSym0 a6989586621680350749 Source #

Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

type Apply (FirstSym0 :: TyFun (Maybe a) (First a) -> Type) (a6989586621680350749 :: Maybe a) = FirstSym1 a6989586621680350749

type FirstSym1 (a6989586621680350749 :: Maybe a) = 'First a6989586621680350749 :: First (a :: Type) Source #

data GetFirstSym0 a6989586621680350752 Source #

Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetFirstSym0 :: TyFun (First a) (Maybe a) -> Type) (a6989586621680350752 :: First a) = GetFirstSym1 a6989586621680350752

type GetFirstSym1 (a6989586621680350752 :: First (a :: Type)) = GetFirst a6989586621680350752 :: Maybe a Source #

data LastSym0 a6989586621680350776 Source #

Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

type Apply (LastSym0 :: TyFun (Maybe a) (Last a) -> Type) (a6989586621680350776 :: Maybe a) = LastSym1 a6989586621680350776

type LastSym1 (a6989586621680350776 :: Maybe a) = 'Last a6989586621680350776 :: Last (a :: Type) Source #

data GetLastSym0 a6989586621680350779 Source #

Instances

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

type Apply (GetLastSym0 :: TyFun (Last a) (Maybe a) -> Type) (a6989586621680350779 :: Last a) = GetLastSym1 a6989586621680350779

type GetLastSym1 (a6989586621680350779 :: Last (a :: Type)) = GetLast a6989586621680350779 :: Maybe a Source #

Orphan instances

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 #

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 #

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 #

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 #

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 #

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 #

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Methods

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

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

Methods

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

PEq (First a) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (Last a) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

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

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

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

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

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

Methods

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

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

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

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

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

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

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

POrd (First a) 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 #

POrd (Last a) 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 #

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 #

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 #

SShow (Maybe 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 (Maybe 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 #

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 #

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

Methods

sing :: Sing ('First0 n) Source #

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

Methods

sing :: Sing ('Last0 n) Source #