singletons-2.5: A framework for generating singleton types

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

Data.Singletons.Prelude.Monoid

Contents

Description

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

Synopsis

Documentation

class PSemigroup a => PMonoid (a :: Type) Source #

Associated Types

type Mempty :: a Source #

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

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

Instances
PMonoid Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid () Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid All Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Max a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (WrappedMonoid m) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Option a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Identity a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Dual a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Sum a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Product a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Down a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (a, b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (a ~> b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

PMonoid (Const a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

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

Defined in Data.Singletons.Prelude.Monoid

Associated Types

type Mempty :: a Source #

type Mappend arg arg :: a Source #

type Mconcat arg :: a Source #

class SSemigroup a => SMonoid a where Source #

Minimal complete definition

sMempty

Methods

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

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

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

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

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

Instances
SMonoid Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SMonoid Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SMonoid () Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SMonoid All Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SMonoid Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SMonoid [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Identity

SMonoid (First a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

SMonoid (Last a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Const

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Equations

GetFirst (First field) = field 

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

Equations

GetLast (Last field) = field 

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 SFirst = (Sing :: First a -> Type) Source #

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

Defunctionalization symbols

data MappendSym0 :: forall a6989586621680329525. (~>) a6989586621680329525 ((~>) a6989586621680329525 a6989586621680329525) Source #

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

type Apply (MappendSym0 :: TyFun a6989586621680329525 (a6989586621680329525 ~> a6989586621680329525) -> Type) (arg6989586621680329910 :: a6989586621680329525) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (MappendSym0 :: TyFun a6989586621680329525 (a6989586621680329525 ~> a6989586621680329525) -> Type) (arg6989586621680329910 :: a6989586621680329525) = MappendSym1 arg6989586621680329910

data MappendSym1 (arg6989586621680329910 :: a6989586621680329525) :: (~>) a6989586621680329525 a6989586621680329525 Source #

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sing :: Sing (MappendSym1 d) Source #

SuppressUnusedWarnings (MappendSym1 arg6989586621680329910 :: TyFun a6989586621680329525 a6989586621680329525 -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (MappendSym1 arg6989586621680329910 :: TyFun a a -> Type) (arg6989586621680329911 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Monoid

type Apply (MappendSym1 arg6989586621680329910 :: TyFun a a -> Type) (arg6989586621680329911 :: a) = Mappend arg6989586621680329910 arg6989586621680329911

type MappendSym2 (arg6989586621680329910 :: a6989586621680329525) (arg6989586621680329911 :: a6989586621680329525) = Mappend arg6989586621680329910 arg6989586621680329911 Source #

data MconcatSym0 :: forall a6989586621680329525. (~>) [a6989586621680329525] a6989586621680329525 Source #

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

type MconcatSym1 (arg6989586621680329914 :: [a6989586621680329525]) = Mconcat arg6989586621680329914 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type DualSym1 (t6989586621679820066 :: a6989586621679086865) = Dual t6989586621679820066 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetDualSym1 (a6989586621679820063 :: Dual a6989586621679086865) = GetDual a6989586621679820063 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 (t6989586621679820080 :: Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

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

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

Instances
SuppressUnusedWarnings GetAllSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetAllSym1 (a6989586621679820077 :: All) = GetAll a6989586621679820077 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 (t6989586621679820094 :: Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

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

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

Instances
SuppressUnusedWarnings GetAnySym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

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

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type SumSym1 (t6989586621679820111 :: a6989586621679086850) = Sum t6989586621679820111 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetSumSym1 (a6989586621679820108 :: Sum a6989586621679086850) = GetSum a6989586621679820108 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type ProductSym1 (t6989586621679820128 :: a6989586621679086855) = Product t6989586621679820128 Source #

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

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

Defined in Data.Singletons.Prelude.Semigroup.Internal

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

type GetProductSym1 (a6989586621679820125 :: Product a6989586621679086855) = GetProduct a6989586621679820125 Source #

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

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

type FirstSym1 (t6989586621680333440 :: Maybe a6989586621679086894) = First t6989586621680333440 Source #

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

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

type GetFirstSym1 (a6989586621680333437 :: First a6989586621679086894) = GetFirst a6989586621680333437 Source #

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

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

type LastSym1 (t6989586621680333461 :: Maybe a6989586621679086889) = Last t6989586621680333461 Source #

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

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

type GetLastSym1 (a6989586621680333458 :: Last a6989586621679086889) = GetLast a6989586621680333458 Source #

Orphan instances

SMonad First Source # 
Instance details

SMonad Last Source # 
Instance details

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 #

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 #

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 #

PApplicative First Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PApplicative Last Source # 
Instance details

Associated Types

type Pure arg :: f a Source #

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

type LiftA2 arg arg arg :: f c Source #

type arg *> arg :: f b Source #

type arg <* arg :: f a Source #

PFunctor First Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

PFunctor Last Source # 
Instance details

Associated Types

type Fmap arg arg :: f b Source #

type arg <$ arg :: f a Source #

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Methods

(%~) :: Sing a0 -> Sing b -> Decision (a0 :~: b) Source #

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

Methods

(%~) :: Sing a0 -> Sing b -> Decision (a0 :~: b) Source #

PEq (First a) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

PEq (Last a) Source # 
Instance details

Associated Types

type x == y :: Bool Source #

type x /= y :: Bool Source #

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

Methods

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

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

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

Methods

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

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

SOrd (Maybe a) => SOrd (First a) 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 #

SOrd (Maybe a) => SOrd (Last a) 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 (First a) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

POrd (Last a) Source # 
Instance details

Associated Types

type Compare arg arg :: Ordering Source #

type arg < arg :: Bool Source #

type arg <= arg :: Bool Source #

type arg > arg :: Bool Source #

type arg >= arg :: Bool Source #

type Max arg arg :: a Source #

type Min arg arg :: a Source #

SSemigroup (First a) Source # 
Instance details

Methods

(%<>) :: 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 #

PSemigroup (First a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

PSemigroup (Last a) Source # 
Instance details

Associated Types

type arg <> arg :: a Source #

type Sconcat arg :: a Source #

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

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

PShow (First a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Last a) Source # 
Instance details

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

Methods

sing :: Sing (First0 n) Source #

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

Methods

sing :: Sing (Last0 n) Source #

ShowSing (Maybe a) => 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 #

SingI (TyCon1 (Last :: Maybe a -> Last a) :: Maybe a ~> Last a) Source # 
Instance details

SingI (TyCon1 (First :: Maybe a -> First a) :: Maybe a ~> First a) Source # 
Instance details