singletons-base-3.2: A promoted and singled version of the base library
Copyright(C) 2014 Jan Stolarek Richard Eisenberg
LicenseBSD-style (see LICENSE)
MaintainerJan Stolarek (jan.stolarek@p.lodz.pl)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageGHC2021

Data.Singletons.Base.Enum

Description

Defines the promoted and singleton version of the Bounded and Enum type classes.

While Prelude.Singletons re-exports the promoted and singled versions of Enum, it deliberately avoids re-exporting Succ and Pred, as these are names are likely to clash with code that deals with unary natural numbers. As a result, this module exists to provide Succ and Pred for those who want them.

Synopsis

Documentation

class PBounded a Source #

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

Instances

Instances details
PBounded All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Identity a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

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

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

PBounded (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type MinBound :: a Source #

type MaxBound :: a Source #

class SBounded a where Source #

Methods

sMinBound :: Sing (MinBoundSym0 :: a) :: Type Source #

sMaxBound :: Sing (MaxBoundSym0 :: a) :: Type Source #

Instances

Instances details
SBounded Bool => SBounded All Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded Bool => SBounded Any Source # 
Instance details

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SBounded () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SBounded Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SBounded Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

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

Defined in Data.Semigroup.Singletons.Internal.Wrappers

SBounded (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Functor.Const.Singletons

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

(SBounded a, SBounded b, SBounded c, SBounded d, SBounded e, SBounded f, SBounded g) => SBounded (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

class PEnum a Source #

Associated Types

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

type Succ a = Apply Succ_6989586621679496135Sym0 a

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

type Pred a = Apply Pred_6989586621679496148Sym0 a

type ToEnum (arg :: Natural) :: a Source #

type FromEnum (arg :: a) :: Natural Source #

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

type EnumFromTo a a = Apply (Apply EnumFromTo_6989586621679496158Sym0 a) a

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

type EnumFromThenTo a a a = Apply (Apply (Apply EnumFromThenTo_6989586621679496170Sym0 a) a) a

Instances

Instances details
PEnum Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum Natural Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum (WrappedMonoid a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

PEnum (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

Associated Types

type Succ arg :: a Source #

type Pred arg :: a Source #

type ToEnum arg :: a Source #

type FromEnum arg :: Natural Source #

type EnumFromTo arg arg1 :: [a] Source #

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

class SEnum a where Source #

Minimal complete definition

sToEnum, sFromEnum

Methods

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

default sSucc :: forall (t :: a). (Apply SuccSym0 t :: a) ~ Apply Succ_6989586621679496135Sym0 t => Sing t -> Sing (Apply SuccSym0 t :: a) :: Type Source #

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

default sPred :: forall (t :: a). (Apply PredSym0 t :: a) ~ Apply Pred_6989586621679496148Sym0 t => Sing t -> Sing (Apply PredSym0 t :: a) :: Type Source #

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

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

sEnumFromTo :: forall (t :: a) (t :: a). Sing t -> Sing t -> Sing (Apply (Apply EnumFromToSym0 t) t :: [a]) :: Type Source #

default sEnumFromTo :: forall (t :: a) (t :: a). (Apply (Apply EnumFromToSym0 t) t :: [a]) ~ Apply (Apply EnumFromTo_6989586621679496158Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply EnumFromToSym0 t) t :: [a]) :: Type Source #

sEnumFromThenTo :: forall (t :: a) (t :: a) (t :: a). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t) t) t :: [a]) :: Type Source #

default sEnumFromThenTo :: forall (t :: a) (t :: a) (t :: a). (Apply (Apply (Apply EnumFromThenToSym0 t) t) t :: [a]) ~ Apply (Apply (Apply EnumFromThenTo_6989586621679496170Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t) t) t :: [a]) :: Type Source #

Instances

Instances details
SEnum Ordering Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

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

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

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

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

sEnumFromTo :: forall (t1 :: Ordering) (t2 :: Ordering). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Ordering) (t2 :: Ordering) (t3 :: Ordering). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

SEnum Natural Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

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

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

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

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

sEnumFromTo :: forall (t1 :: Natural) (t2 :: Natural). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Natural) (t2 :: Natural) (t3 :: Natural). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

SEnum () Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

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

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

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

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

sEnumFromTo :: forall (t1 :: ()) (t2 :: ()). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: ()) (t2 :: ()) (t3 :: ()). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

SEnum Bool Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

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

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

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

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

sEnumFromTo :: forall (t1 :: Bool) (t2 :: Bool). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Bool) (t2 :: Bool) (t3 :: Bool). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

SEnum Char Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

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

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

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

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

sEnumFromTo :: forall (t1 :: Char) (t2 :: Char). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Char) (t2 :: Char) (t3 :: Char). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

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

Defined in Data.Functor.Identity.Singletons

Methods

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

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

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

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

sEnumFromTo :: forall (t1 :: Identity a) (t2 :: Identity a). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Identity a) (t2 :: Identity a) (t3 :: Identity a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

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

Defined in Data.Semigroup.Singletons

Methods

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

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

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

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

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

sEnumFromThenTo :: forall (t1 :: First a) (t2 :: First a) (t3 :: First a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

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

Defined in Data.Semigroup.Singletons

Methods

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

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

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

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

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

sEnumFromThenTo :: forall (t1 :: Last a) (t2 :: Last a) (t3 :: Last a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

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

Defined in Data.Semigroup.Singletons

Methods

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

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

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

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

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

sEnumFromThenTo :: forall (t1 :: Max a) (t2 :: Max a) (t3 :: Max a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

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

Defined in Data.Semigroup.Singletons

Methods

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

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

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

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

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

sEnumFromThenTo :: forall (t1 :: Min a) (t2 :: Min a) (t3 :: Min a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

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

Defined in Data.Semigroup.Singletons

Methods

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

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

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

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

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

sEnumFromThenTo :: forall (t1 :: WrappedMonoid a) (t2 :: WrappedMonoid a) (t3 :: WrappedMonoid a). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

SEnum (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sSucc :: forall (t :: Proxy s). Sing t -> Sing (Apply SuccSym0 t) Source #

sPred :: forall (t :: Proxy s). Sing t -> Sing (Apply PredSym0 t) Source #

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

sFromEnum :: forall (t :: Proxy s). Sing t -> Sing (Apply FromEnumSym0 t) Source #

sEnumFromTo :: forall (t1 :: Proxy s) (t2 :: Proxy s). Sing t1 -> Sing t2 -> Sing (Apply (Apply EnumFromToSym0 t1) t2) Source #

sEnumFromThenTo :: forall (t1 :: Proxy s) (t2 :: Proxy s) (t3 :: Proxy s). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

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

Defined in Data.Functor.Const.Singletons

Methods

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

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

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

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

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

sEnumFromThenTo :: forall (t1 :: Const a b) (t2 :: Const a b) (t3 :: Const a b). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply EnumFromThenToSym0 t1) t2) t3) Source #

Defunctionalization symbols

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

Equations

MinBoundSym0 = MinBound 

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

Equations

MaxBoundSym0 = MaxBound 

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

Instances

Instances details
SEnum a => SingI (SuccSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing SuccSym0 #

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

Defined in Data.Singletons.Base.Enum

type Apply (SuccSym0 :: TyFun a a -> Type) (a6989586621679496112 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (SuccSym0 :: TyFun a a -> Type) (a6989586621679496112 :: a) = Succ a6989586621679496112

type family SuccSym1 (a6989586621679496112 :: a) :: a where ... Source #

Equations

SuccSym1 a6989586621679496112 = Succ a6989586621679496112 

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

Instances

Instances details
SEnum a => SingI (PredSym0 :: TyFun a a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing PredSym0 #

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

Defined in Data.Singletons.Base.Enum

type Apply (PredSym0 :: TyFun a a -> Type) (a6989586621679496115 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (PredSym0 :: TyFun a a -> Type) (a6989586621679496115 :: a) = Pred a6989586621679496115

type family PredSym1 (a6989586621679496115 :: a) :: a where ... Source #

Equations

PredSym1 a6989586621679496115 = Pred a6989586621679496115 

data ToEnumSym0 :: (~>) Natural a Source #

Instances

Instances details
SEnum a => SingI (ToEnumSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing ToEnumSym0 #

SuppressUnusedWarnings (ToEnumSym0 :: TyFun Natural a -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (ToEnumSym0 :: TyFun Natural k2 -> Type) (a6989586621679496118 :: Natural) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (ToEnumSym0 :: TyFun Natural k2 -> Type) (a6989586621679496118 :: Natural) = ToEnum a6989586621679496118 :: k2

type family ToEnumSym1 (a6989586621679496118 :: Natural) :: a where ... Source #

Equations

ToEnumSym1 a6989586621679496118 = ToEnum a6989586621679496118 

data FromEnumSym0 :: (~>) a Natural Source #

Instances

Instances details
SEnum a => SingI (FromEnumSym0 :: TyFun a Natural -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (FromEnumSym0 :: TyFun a Natural -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (FromEnumSym0 :: TyFun a Natural -> Type) (a6989586621679496121 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (FromEnumSym0 :: TyFun a Natural -> Type) (a6989586621679496121 :: a) = FromEnum a6989586621679496121

type family FromEnumSym1 (a6989586621679496121 :: a) :: Natural where ... Source #

Equations

FromEnumSym1 a6989586621679496121 = FromEnum a6989586621679496121 

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

Instances

Instances details
SEnum a => SingI (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679496125 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym0 :: TyFun a (a ~> [a]) -> Type) (a6989586621679496125 :: a) = EnumFromToSym1 a6989586621679496125

data EnumFromToSym1 (a6989586621679496125 :: a) :: (~>) a [a] Source #

Instances

Instances details
SEnum a => SingI1 (EnumFromToSym1 :: a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (EnumFromToSym1 x) #

(SEnum a, SingI d) => SingI (EnumFromToSym1 d :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromToSym1 d) #

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

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym1 a6989586621679496125 :: TyFun a [a] -> Type) (a6989586621679496126 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromToSym1 a6989586621679496125 :: TyFun a [a] -> Type) (a6989586621679496126 :: a) = EnumFromTo a6989586621679496125 a6989586621679496126

type family EnumFromToSym2 (a6989586621679496125 :: a) (a6989586621679496126 :: a) :: [a] where ... Source #

Equations

EnumFromToSym2 a6989586621679496125 a6989586621679496126 = EnumFromTo a6989586621679496125 a6989586621679496126 

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

Instances

Instances details
SEnum a => SingI (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

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

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679496131 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym0 :: TyFun a (a ~> (a ~> [a])) -> Type) (a6989586621679496131 :: a) = EnumFromThenToSym1 a6989586621679496131

data EnumFromThenToSym1 (a6989586621679496131 :: a) :: (~>) a ((~>) a [a]) Source #

Instances

Instances details
SEnum a => SingI1 (EnumFromThenToSym1 :: a -> TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (EnumFromThenToSym1 x) #

(SEnum a, SingI d) => SingI (EnumFromThenToSym1 d :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

SuppressUnusedWarnings (EnumFromThenToSym1 a6989586621679496131 :: TyFun a (a ~> [a]) -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679496131 :: TyFun a (a ~> [a]) -> Type) (a6989586621679496132 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym1 a6989586621679496131 :: TyFun a (a ~> [a]) -> Type) (a6989586621679496132 :: a) = EnumFromThenToSym2 a6989586621679496131 a6989586621679496132

data EnumFromThenToSym2 (a6989586621679496131 :: a) (a6989586621679496132 :: a) :: (~>) a [a] Source #

Instances

Instances details
SEnum a => SingI2 (EnumFromThenToSym2 :: a -> a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing2 :: forall (x :: k1) (y :: k2). Sing x -> Sing y -> Sing (EnumFromThenToSym2 x y) #

(SEnum a, SingI d) => SingI1 (EnumFromThenToSym2 d :: a -> TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

liftSing :: forall (x :: k1). Sing x -> Sing (EnumFromThenToSym2 d x) #

(SEnum a, SingI d1, SingI d2) => SingI (EnumFromThenToSym2 d1 d2 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

Methods

sing :: Sing (EnumFromThenToSym2 d1 d2) #

SuppressUnusedWarnings (EnumFromThenToSym2 a6989586621679496131 a6989586621679496132 :: TyFun a [a] -> Type) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym2 a6989586621679496131 a6989586621679496132 :: TyFun a [a] -> Type) (a6989586621679496133 :: a) Source # 
Instance details

Defined in Data.Singletons.Base.Enum

type Apply (EnumFromThenToSym2 a6989586621679496131 a6989586621679496132 :: TyFun a [a] -> Type) (a6989586621679496133 :: a) = EnumFromThenTo a6989586621679496131 a6989586621679496132 a6989586621679496133

type family EnumFromThenToSym3 (a6989586621679496131 :: a) (a6989586621679496132 :: a) (a6989586621679496133 :: a) :: [a] where ... Source #

Equations

EnumFromThenToSym3 a6989586621679496131 a6989586621679496132 a6989586621679496133 = EnumFromThenTo a6989586621679496131 a6989586621679496132 a6989586621679496133