singletons-2.5.1: A framework for generating singleton types

Copyright(C) 2018 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.Semigroup

Contents

Description

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

Synopsis

Documentation

class PSemigroup (a :: Type) Source #

Associated Types

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

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

Instances
PSemigroup Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup () Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup All Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (WrappedMonoid m) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Identity a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Dual a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Sum a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Product a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Down a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (a, b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (a ~> b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Const a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

class SSemigroup a where Source #

Minimal complete definition

(%<>)

Methods

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

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

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

Instances
SSemigroup Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup () Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup All Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

SSemigroup (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

SSemigroup (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

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

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

Defined in Data.Singletons.Prelude.Identity

Methods

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

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

SSemigroup (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

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

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

SSemigroup (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

SSemigroup (Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Const

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

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

data family Sing :: k -> Type Source #

The singleton kind-indexed data family.

Instances
SDecide k => TestCoercion (Sing :: k -> Type) Source # 
Instance details

Defined in Data.Singletons.Decide

Methods

testCoercion :: Sing a -> Sing b -> Maybe (Coercion a b) #

SDecide k => TestEquality (Sing :: k -> Type) Source # 
Instance details

Defined in Data.Singletons.Decide

Methods

testEquality :: Sing a -> Sing b -> Maybe (a :~: b) #

Show (SSymbol s) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> SSymbol s -> ShowS #

show :: SSymbol s -> String #

showList :: [SSymbol s] -> ShowS #

Show (SNat n) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsPrec :: Int -> SNat n -> ShowS #

show :: SNat n -> String #

showList :: [SNat n] -> ShowS #

Eq (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

(==) :: Sing a -> Sing a -> Bool #

(/=) :: Sing a -> Sing a -> Bool #

Ord (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

compare :: Sing a -> Sing a -> Ordering #

(<) :: Sing a -> Sing a -> Bool #

(<=) :: Sing a -> Sing a -> Bool #

(>) :: Sing a -> Sing a -> Bool #

(>=) :: Sing a -> Sing a -> Bool #

max :: Sing a -> Sing a -> Sing a #

min :: Sing a -> Sing a -> Sing a #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing [a]) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing a) Source # 
Instance details

Defined in Data.Singletons.TypeRepTYPE

Methods

showsPrec :: Int -> Sing a -> ShowS #

show :: Sing a -> String #

showList :: [Sing a] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing b, ShowSing c, ShowSing d, ShowSing e, ShowSing f, ShowSing g) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Monoid

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Monoid

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

(ShowSing a, ShowSing [a]) => Show (Sing z) Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

data Sing (a :: Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Bool) where
data Sing (a :: Ordering) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Ordering) where
data Sing (n :: Nat) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

data Sing (n :: Nat) where
data Sing (n :: Symbol) Source # 
Instance details

Defined in Data.Singletons.TypeLits.Internal

data Sing (n :: Symbol) where
data Sing (a :: ()) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: ()) where
data Sing (a :: Void) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (a :: Void)
data Sing (a :: All) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: All) where
data Sing (a :: Any) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: Any) where
data Sing (a :: PErrorMessage) Source # 
Instance details

Defined in Data.Singletons.TypeError

data Sing (a :: PErrorMessage) where
data Sing (b :: [a]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: [a]) where
  • SNil :: forall k (b :: [k]). Sing ([] :: [k])
  • SCons :: forall a (b :: [a]) (n :: a) (n :: [a]). Sing n -> Sing n -> Sing (n ': n)
data Sing (b :: Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: Maybe a) where
data Sing (a :: TYPE rep) 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 -> Type` 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

data Sing (a :: TYPE rep) = STypeRep (TypeRep a)
data Sing (b :: Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Min a) where
data Sing (b :: Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Max a) where
data Sing (b :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: First a) where
data Sing (b :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Last a) where
data Sing (a :: WrappedMonoid m) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (a :: WrappedMonoid m) where
data Sing (b :: Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Option a) where
data Sing (b :: Identity a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: Identity a) where
data Sing (b :: First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

data Sing (b :: First a) where
data Sing (b :: Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

data Sing (b :: Last a) where
data Sing (b :: Dual a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Dual a) where
data Sing (b :: Sum a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Sum a) where
data Sing (b :: Product a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

data Sing (b :: Product a) where
data Sing (b :: Down a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Ord

data Sing (b :: Down a) where
data Sing (b :: NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (b :: NonEmpty a) where
data Sing (c :: Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (c :: Either a b) where
data Sing (c :: (a, b)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (c :: (a, b)) where
data Sing (c :: Arg a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

data Sing (c :: Arg a b) where
data Sing (f :: k1 ~> k2) Source # 
Instance details

Defined in Data.Singletons.Internal

data Sing (f :: k1 ~> k2) = SLambda {}
data Sing (d :: (a, b, c)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (d :: (a, b, c)) where
data Sing (c :: Const a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

data Sing (c :: Const a b) where
data Sing (e :: (a, b, c, d)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (e :: (a, b, c, d)) where
data Sing (f :: (a, b, c, d, e)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (f :: (a, b, c, d, e)) where
data Sing (g :: (a, b, c, d, e, f)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (g :: (a, b, c, d, e, f)) where
data Sing (h :: (a, b, c, d, e, f, g)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Instances

data Sing (h :: (a, b, c, d, e, f, g)) where

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

Equations

GetMin (Min field) = field 

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

Equations

GetMax (Max field) = field 

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

Equations

GetFirst (First field) = field 

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

Equations

GetLast (Last field) = field 

type family GetDual (a :: Dual a) :: 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) :: a where ... Source #

Equations

GetSum (Sum field) = field 

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

Equations

GetProduct (Product field) = field 

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

Equations

GetOption (Option field) = field 

type SMin = (Sing :: Min a -> Type) Source #

type SMax = (Sing :: Max a -> Type) Source #

type SFirst = (Sing :: First a -> Type) Source #

type SLast = (Sing :: Last a -> Type) Source #

type SDual = (Sing :: Dual a -> Type) Source #

type SAll = (Sing :: All -> Type) Source #

type SAny = (Sing :: Any -> Type) Source #

type SSum = (Sing :: Sum a -> Type) Source #

type SProduct = (Sing :: Product a -> Type) Source #

type SOption = (Sing :: Option a -> Type) Source #

type SArg = (Sing :: Arg a b -> Type) Source #

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

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

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

Equations

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

Defunctionalization symbols

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply ((<>@#@$) :: TyFun a6989586621679800518 (a6989586621679800518 ~> a6989586621679800518) -> Type) (arg6989586621679801003 :: a6989586621679800518) = (<>@#@$$) arg6989586621679801003

data (<>@#@$$) (arg6989586621679801003 :: a6989586621679800518) :: (~>) a6989586621679800518 a6989586621679800518 infixr 6 Source #

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

Methods

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

SuppressUnusedWarnings ((<>@#@$$) arg6989586621679801003 :: TyFun a6989586621679800518 a6989586621679800518 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply ((<>@#@$$) arg6989586621679801003 :: TyFun a a -> Type) (arg6989586621679801004 :: a) = arg6989586621679801003 <> arg6989586621679801004

type (<>@#@$$$) (arg6989586621679801003 :: a6989586621679800518) (arg6989586621679801004 :: a6989586621679800518) = (<>) arg6989586621679801003 arg6989586621679801004 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type SconcatSym1 (arg6989586621679801007 :: NonEmpty a6989586621679800518) = Sconcat arg6989586621679801007 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type MinSym1 (t6989586621679810306 :: a6989586621679061210) = Min t6989586621679810306 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetMinSym1 (a6989586621679810303 :: Min a6989586621679061210) = GetMin a6989586621679810303 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type MaxSym1 (t6989586621679810323 :: a6989586621679061216) = Max t6989586621679810323 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetMaxSym1 (a6989586621679810320 :: Max a6989586621679061216) = GetMax a6989586621679810320 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type FirstSym1 (t6989586621679810340 :: a6989586621679061230) = First t6989586621679810340 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetFirstSym1 (a6989586621679810337 :: First a6989586621679061230) = GetFirst a6989586621679810337 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type LastSym1 (t6989586621679810357 :: a6989586621679061236) = Last t6989586621679810357 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetLastSym1 (a6989586621679810354 :: Last a6989586621679061236) = GetLast a6989586621679810354 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type WrapMonoidSym1 (t6989586621679810374 :: m6989586621679061242) = WrapMonoid t6989586621679810374 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply (UnwrapMonoidSym0 :: TyFun (WrappedMonoid m) m -> Type) (a6989586621679810371 :: WrappedMonoid m)

type UnwrapMonoidSym1 (a6989586621679810371 :: WrappedMonoid m6989586621679061242) = UnwrapMonoid a6989586621679810371 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type DualSym1 (t6989586621679810227 :: a6989586621679081576) = Dual t6989586621679810227 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetDualSym1 (a6989586621679810224 :: Dual a6989586621679081576) = GetDual a6989586621679810224 Source #

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

Instances
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 (t6989586621679810241 :: Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AllSym0 (t6989586621679810241 :: Bool) = All t6989586621679810241

type AllSym1 (t6989586621679810241 :: Bool) = All t6989586621679810241 Source #

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

Instances
SuppressUnusedWarnings GetAllSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

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

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

Instances
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 (t6989586621679810255 :: Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

type Apply AnySym0 (t6989586621679810255 :: Bool) = Any t6989586621679810255

type AnySym1 (t6989586621679810255 :: Bool) = Any t6989586621679810255 Source #

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

Instances
SuppressUnusedWarnings GetAnySym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type SumSym1 (t6989586621679810272 :: a6989586621679081561) = Sum t6989586621679810272 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetSumSym1 (a6989586621679810269 :: Sum a6989586621679081561) = GetSum a6989586621679810269 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type ProductSym1 (t6989586621679810289 :: a6989586621679081566) = Product t6989586621679810289 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetProductSym1 (a6989586621679810286 :: Product a6989586621679081566) = GetProduct a6989586621679810286 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type OptionSym1 (t6989586621679810210 :: Maybe a6989586621679061248) = Option t6989586621679810210 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetOptionSym1 (a6989586621679810207 :: Option a6989586621679061248) = GetOption a6989586621679810207 Source #

data ArgSym0 :: forall (a6989586621679061223 :: Type) (b6989586621679061224 :: Type). (~>) a6989586621679061223 ((~>) b6989586621679061224 (Arg (a6989586621679061223 :: Type) (b6989586621679061224 :: Type))) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

SuppressUnusedWarnings (ArgSym0 :: TyFun a6989586621679061223 (b6989586621679061224 ~> Arg a6989586621679061223 b6989586621679061224) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (ArgSym0 :: TyFun a6989586621679061223 (b6989586621679061224 ~> Arg a6989586621679061223 b6989586621679061224) -> Type) (t6989586621680850272 :: a6989586621679061223) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

type Apply (ArgSym0 :: TyFun a6989586621679061223 (b6989586621679061224 ~> Arg a6989586621679061223 b6989586621679061224) -> Type) (t6989586621680850272 :: a6989586621679061223) = (ArgSym1 t6989586621680850272 b6989586621679061224 :: TyFun b6989586621679061224 (Arg a6989586621679061223 b6989586621679061224) -> Type)

data ArgSym1 (t6989586621680850272 :: (a6989586621679061223 :: Type)) :: forall (b6989586621679061224 :: Type). (~>) b6989586621679061224 (Arg (a6989586621679061223 :: Type) (b6989586621679061224 :: Type)) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sing :: Sing (ArgSym1 d b) Source #

SuppressUnusedWarnings (ArgSym1 t6989586621680850272 b6989586621679061224 :: TyFun b6989586621679061224 (Arg a6989586621679061223 b6989586621679061224) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

type Apply (ArgSym1 t6989586621680850272 b :: TyFun b (Arg a b) -> Type) (t6989586621680850273 :: b) = Arg t6989586621680850272 t6989586621680850273

type ArgSym2 (t6989586621680850272 :: a6989586621679061223) (t6989586621680850273 :: b6989586621679061224) = Arg t6989586621680850272 t6989586621680850273 Source #

Orphan instances

SMonadPlus Option Source # 
Instance details

SAlternative Option Source # 
Instance details

SMonad Min Source # 
Instance details

SMonad Max Source # 
Instance details

SMonad First Source # 
Instance details

SMonad Last Source # 
Instance details

SMonad Option Source # 
Instance details

SApplicative Min Source # 
Instance details

Methods

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

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

sLiftA2 :: Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

(%*>) :: Sing t -> Sing t -> Sing (Apply (Apply (*>@#@$) t) t) Source #

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

SApplicative Max Source # 
Instance details

Methods

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

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

sLiftA2 :: Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

(%*>) :: Sing t -> Sing t -> Sing (Apply (Apply (*>@#@$) t) t) Source #

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

SApplicative First Source # 
Instance details

Methods

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

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

sLiftA2 :: Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

(%*>) :: Sing t -> Sing t -> Sing (Apply (Apply (*>@#@$) t) t) Source #

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

SApplicative Last Source # 
Instance details

Methods

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

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

sLiftA2 :: Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

(%*>) :: Sing t -> Sing t -> Sing (Apply (Apply (*>@#@$) t) t) Source #

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

SApplicative Option Source # 
Instance details

Methods

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

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

sLiftA2 :: Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply LiftA2Sym0 t) t) t) Source #

(%*>) :: Sing t -> Sing t -> Sing (Apply (Apply (*>@#@$) t) t) Source #

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

SFunctor Min Source # 
Instance details

Methods

sFmap :: Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

SFunctor Max Source # 
Instance details

Methods

sFmap :: Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

SFunctor First Source # 
Instance details

Methods

sFmap :: Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

SFunctor Last Source # 
Instance details

Methods

sFmap :: Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

SFunctor Option Source # 
Instance details

Methods

sFmap :: Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

PMonadPlus Option Source # 
Instance details

Associated Types

type Mzero :: m a Source #

type Mplus arg arg :: m a Source #

PAlternative Option Source # 
Instance details

Associated Types

type Empty :: f a Source #

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

PMonad Min Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

type Fail arg :: m a Source #

PMonad Max Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

type Fail arg :: m a Source #

PMonad First Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

type Fail 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 #

type Fail arg :: m a Source #

PMonad Option Source # 
Instance details

Associated Types

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

type arg >> arg :: m b Source #

type Return arg :: m a Source #

type Fail arg :: m a Source #

PApplicative Min Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative Max Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative First Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative Last Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative Option Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PFunctor Min Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor Max Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor First Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor Last Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor Option Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

SShow Bool => SShow All Source # 
Instance details

SShow Bool => SShow Any Source # 
Instance details

PShow All Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Any Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

SFoldable Min Source # 
Instance details

SFoldable Max Source # 
Instance details

SFoldable First Source # 
Instance details

SFoldable Last Source # 
Instance details

SFoldable Option Source # 
Instance details

PFoldable Min Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Max Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable First Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Last Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

PFoldable Option Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

STraversable Min Source # 
Instance details

STraversable Max Source # 
Instance details

STraversable First Source # 
Instance details

STraversable Last Source # 
Instance details

STraversable Option Source # 
Instance details

PTraversable Min Source # 
Instance details

Associated Types

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

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

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

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

PTraversable Max Source # 
Instance details

Associated Types

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

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

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

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

PTraversable First Source # 
Instance details

Associated Types

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

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

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

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

PTraversable Last Source # 
Instance details

Associated Types

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

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

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

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

PTraversable Option Source # 
Instance details

Associated Types

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

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

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

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

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

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

PNum (Min a) Source # 
Instance details

Associated Types

type arg + arg :: a Source #

type arg - arg :: a Source #

type arg * arg :: a Source #

type Negate arg :: a Source #

type Abs arg :: a Source #

type Signum arg :: a Source #

type FromInteger arg :: a Source #

PNum (Max a) Source # 
Instance details

Associated Types

type arg + arg :: a Source #

type arg - arg :: a Source #

type arg * arg :: a Source #

type Negate arg :: a Source #

type Abs arg :: a Source #

type Signum arg :: a Source #

type FromInteger arg :: a Source #

SFunctor (Arg a) Source # 
Instance details

Methods

sFmap :: Sing t -> Sing t -> Sing (Apply (Apply FmapSym0 t) t) Source #

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

PFunctor (Arg a) Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

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

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

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

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

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

PEnum (Min a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

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

PEnum (Max a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

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

PEnum (First a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

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

PEnum (Last a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

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

PEnum (WrappedMonoid a) Source # 
Instance details

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Nat Source #

type EnumFromTo arg arg :: [a] Source #

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

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

Methods

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

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

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

Methods

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

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

SSemigroup (First a) Source # 
Instance details

Methods

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

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

SSemigroup (Last a) Source # 
Instance details

Methods

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

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

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

Methods

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

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

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

Methods

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

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

PSemigroup (Min a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Max a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (First a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (WrappedMonoid m) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Option a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

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

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

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

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

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

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

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

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

PShow (Min a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Max a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (First a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Last a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (WrappedMonoid m) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Option a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Dual a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Sum a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Product a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

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

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

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

PMonoid (Min a) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Max a) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (WrappedMonoid m) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Option a) Source # 
Instance details

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

SFoldable (Arg a) Source # 
Instance details

PFoldable (Arg a) Source # 
Instance details

Associated Types

type Fold arg :: m Source #

type FoldMap arg arg :: m Source #

type Foldr arg arg arg :: b Source #

type Foldr' arg arg arg :: b Source #

type Foldl arg arg arg :: b Source #

type Foldl' arg arg arg :: b Source #

type Foldr1 arg arg :: a Source #

type Foldl1 arg arg :: a Source #

type ToList arg :: [a] Source #

type Null arg :: Bool Source #

type Length arg :: Nat Source #

type Elem arg arg :: Bool Source #

type Maximum arg :: a Source #

type Minimum arg :: a Source #

type Sum arg :: a Source #

type Product arg :: a Source #

STraversable (Arg a) Source # 
Instance details

PTraversable (Arg a) Source # 
Instance details

Associated Types

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

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

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

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

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Associated Types

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

Methods

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

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

PEq (Arg a b) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

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

Methods

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) Source #

(%/=) :: Sing a0 -> Sing b0 -> Sing (a0 /= b0) Source #

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

Methods

sCompare :: Sing t -> Sing t -> Sing (Apply (Apply CompareSym0 t) t) Source #

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

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

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

(%>=) :: Sing t -> Sing t -> Sing (Apply (Apply (>=@#@$) t) t) Source #

sMax :: Sing t -> Sing t -> Sing (Apply (Apply MaxSym0 t) t) Source #

sMin :: Sing t -> Sing t -> Sing (Apply (Apply MinSym0 t) t) Source #

POrd (Arg a b) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

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

PShow (Arg a b) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

SingI d => SingI (TyCon1 (Arg d :: b -> Arg a b) :: b ~> Arg a b) Source # 
Instance details

Methods

sing :: Sing (TyCon1 (Arg0 d)) Source #

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

Methods

sing :: Sing (Arg0 n1 n2) Source #

SingI (TyCon2 (Arg :: a -> b -> Arg a b) :: a ~> (b ~> Arg a b)) Source # 
Instance details

Methods

sing :: Sing (TyCon2 Arg0) Source #