singletons-2.6: A framework for generating singleton types
Copyright(C) 2017 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.Prelude.Show

Description

Defines the SShow singleton version of the Show type class.

Synopsis

Documentation

class PShow (a :: Type) Source #

Associated Types

type ShowsPrec (arg :: Nat) (arg :: a) (arg :: Symbol) :: Symbol Source #

type ShowsPrec a a a = Apply (Apply (Apply ShowsPrec_6989586621680295074Sym0 a) a) a Source #

type Show_ (arg :: a) :: Symbol Source #

type Show_ a = Apply Show__6989586621680295088Sym0 a Source #

type ShowList (arg :: [a]) (arg :: Symbol) :: Symbol Source #

type ShowList a a = Apply (Apply ShowList_6989586621680295096Sym0 a) a Source #

Instances

Instances details
PShow Bool Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Nat Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow () Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow All Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Maybe a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Min a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Identity a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Identity

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Monoid

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

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

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Either a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (a, b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Arg a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

PShow (Const a b) Source # 
Instance details

Defined in Data.Singletons.Prelude.Const

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

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

Defined in Data.Singletons.Prelude.Show

Associated Types

type ShowsPrec arg arg arg :: Symbol Source #

type Show_ arg :: Symbol Source #

type ShowList arg arg :: Symbol Source #

class SShow a where Source #

Minimal complete definition

Nothing

Methods

sShowsPrec :: forall (t :: Nat) (t :: a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t :: Symbol) Source #

default sShowsPrec :: forall (t :: Nat) (t :: a) (t :: Symbol). (Apply (Apply (Apply ShowsPrecSym0 t) t) t :: Symbol) ~ Apply (Apply (Apply ShowsPrec_6989586621680295074Sym0 t) t) t => Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t :: Symbol) Source #

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

default sShow_ :: forall (t :: a). (Apply Show_Sym0 t :: Symbol) ~ Apply Show__6989586621680295088Sym0 t => Sing t -> Sing (Apply Show_Sym0 t :: Symbol) Source #

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

default sShowList :: forall (t :: [a]) (t :: Symbol). (Apply (Apply ShowListSym0 t) t :: Symbol) ~ Apply (Apply ShowList_6989586621680295096Sym0 t) t => Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t :: Symbol) Source #

Instances

Instances details
SShow Bool Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: Bool) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Bool]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow Ordering Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: Ordering) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Ordering]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow Nat Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: Nat) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Nat]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow Symbol Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Symbol]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow () Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: ()) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [()]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow Void Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: Void) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Void]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow Bool => SShow All Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: All) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [All]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow Bool => SShow Any Source # 
Instance details

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Any) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Any]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

SShow a => SShow [a] Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: [a]) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

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

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

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: Maybe a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Maybe a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Min a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Min a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Max a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Max a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: First a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Last a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: WrappedMonoid m) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

sShow_ :: forall (t :: WrappedMonoid m). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t :: [WrappedMonoid m]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Option a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Option a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Identity

Methods

sShowsPrec :: forall (t :: Nat) (t :: Identity a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Identity a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sShowsPrec :: forall (t :: Nat) (t :: First a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

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

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

Defined in Data.Singletons.Prelude.Monoid

Methods

sShowsPrec :: forall (t :: Nat) (t :: Last a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

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

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Dual a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Dual a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Sum a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Sum a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Product a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Product a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

(SShow a, SShow [a]) => SShow (NonEmpty a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: NonEmpty a) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [NonEmpty a]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: Either a b) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Either a b]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: (a, b)) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [(a, b)]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Semigroup

Methods

sShowsPrec :: forall (t :: Nat) (t :: Arg a b) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Arg a b]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: (a, b, c)) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [(a, b, c)]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Const

Methods

sShowsPrec :: forall (t :: Nat) (t :: Const a b) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

sShowList :: forall (t :: [Const a b]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: (a, b, c, d)) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

sShow_ :: forall (t :: (a, b, c, d)). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t :: [(a, b, c, d)]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: (a, b, c, d, e)) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

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

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

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

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: (a, b, c, d, e, f)) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

sShow_ :: forall (t :: (a, b, c, d, e, f)). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t :: [(a, b, c, d, e, f)]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

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

Defined in Data.Singletons.Prelude.Show

Methods

sShowsPrec :: forall (t :: Nat) (t :: (a, b, c, d, e, f, g)) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowsPrecSym0 t) t) t) Source #

sShow_ :: forall (t :: (a, b, c, d, e, f, g)). Sing t -> Sing (Apply Show_Sym0 t) Source #

sShowList :: forall (t :: [(a, b, c, d, e, f, g)]) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowListSym0 t) t) Source #

type SymbolS = Symbol -> Symbol Source #

The shows functions return a function that prepends the output Symbol to an existing Symbol. This allows constant-time concatenation of results using function composition.

type SChar = Symbol Source #

GHC currently has no notion of type-level Chars, so we fake them with single-character Symbols.

show_ :: Show a => a -> String Source #

show, but with an extra underscore so that its promoted counterpart (Show_) will not clash with the Show class.

type family Shows (a :: a) (a :: Symbol) :: Symbol where ... Source #

Equations

Shows s a_6989586621680295055 = Apply (Apply (Apply ShowsPrecSym0 (FromInteger 0)) s) a_6989586621680295055 

sShows :: forall a (t :: a) (t :: Symbol). SShow a => Sing t -> Sing t -> Sing (Apply (Apply ShowsSym0 t) t :: Symbol) Source #

type family ShowListWith (a :: (~>) a ((~>) Symbol Symbol)) (a :: [a]) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowListWith _ '[] s = Apply (Apply (<>@#@$) "[]") s 
ShowListWith showx ('(:) x xs) s = Apply (Apply (<>@#@$) "[") (Apply (Apply showx x) (Apply (Let6989586621680295042ShowlSym4 showx x xs s) xs)) 

sShowListWith :: forall a (t :: (~>) a ((~>) Symbol Symbol)) (t :: [a]) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowListWithSym0 t) t) t :: Symbol) Source #

type family ShowChar (a :: Symbol) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowChar a_6989586621680295021 a_6989586621680295023 = Apply (Apply (<>@#@$) a_6989586621680295021) a_6989586621680295023 

sShowChar :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowCharSym0 t) t :: Symbol) Source #

type family ShowString (a :: Symbol) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowString a_6989586621680295011 a_6989586621680295013 = Apply (Apply (<>@#@$) a_6989586621680295011) a_6989586621680295013 

sShowString :: forall (t :: Symbol) (t :: Symbol). Sing t -> Sing t -> Sing (Apply (Apply ShowStringSym0 t) t :: Symbol) Source #

type family ShowParen (a :: Bool) (a :: (~>) Symbol Symbol) (a :: Symbol) :: Symbol where ... Source #

Equations

ShowParen b p a_6989586621680295003 = Apply (Case_6989586621680295008 b p a_6989586621680295003 b) a_6989586621680295003 

sShowParen :: forall (t :: Bool) (t :: (~>) Symbol Symbol) (t :: Symbol). Sing t -> Sing t -> Sing t -> Sing (Apply (Apply (Apply ShowParenSym0 t) t) t :: Symbol) Source #

type family ShowSpace (a :: Symbol) :: Symbol where ... Source #

Equations

ShowSpace a_6989586621680294986 = Apply (Apply Lambda_6989586621680294991Sym0 a_6989586621680294986) a_6989586621680294986 

sShowSpace :: forall (t :: Symbol). Sing t -> Sing (Apply ShowSpaceSym0 t :: Symbol) Source #

type family ShowCommaSpace (a :: Symbol) :: Symbol where ... Source #

Equations

ShowCommaSpace a_6989586621680294981 = Apply (Apply ShowStringSym0 ", ") a_6989586621680294981 

type family AppPrec :: Nat where ... Source #

Equations

AppPrec = FromInteger 10 

type family AppPrec1 :: Nat where ... Source #

Equations

AppPrec1 = FromInteger 11 

Defunctionalization symbols

data ShowsPrecSym0 :: forall a6989586621680294621. (~>) Nat ((~>) a6989586621680294621 ((~>) Symbol Symbol)) Source #

Instances

Instances details
SShow a => SingI (ShowsPrecSym0 :: TyFun Nat (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Nat (a6989586621680294621 ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym0 :: TyFun Nat (a6989586621680294621 ~> (Symbol ~> Symbol)) -> Type) (arg6989586621680295059 :: Nat) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym0 :: TyFun Nat (a6989586621680294621 ~> (Symbol ~> Symbol)) -> Type) (arg6989586621680295059 :: Nat) = ShowsPrecSym1 arg6989586621680295059 a6989586621680294621 :: TyFun a6989586621680294621 (Symbol ~> Symbol) -> Type

data ShowsPrecSym1 (arg6989586621680295059 :: Nat) :: forall a6989586621680294621. (~>) a6989586621680294621 ((~>) Symbol Symbol) Source #

Instances

Instances details
(SShow a, SingI d) => SingI (ShowsPrecSym1 d a :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sing :: Sing (ShowsPrecSym1 d a) Source #

SuppressUnusedWarnings (ShowsPrecSym1 arg6989586621680295059 a6989586621680294621 :: TyFun a6989586621680294621 (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym1 arg6989586621680295059 a6989586621680294621 :: TyFun a6989586621680294621 (Symbol ~> Symbol) -> Type) (arg6989586621680295060 :: a6989586621680294621) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym1 arg6989586621680295059 a6989586621680294621 :: TyFun a6989586621680294621 (Symbol ~> Symbol) -> Type) (arg6989586621680295060 :: a6989586621680294621) = ShowsPrecSym2 arg6989586621680295059 arg6989586621680295060

data ShowsPrecSym2 (arg6989586621680295059 :: Nat) (arg6989586621680295060 :: a6989586621680294621) :: (~>) Symbol Symbol Source #

Instances

Instances details
(SShow a, SingI d1, SingI d2) => SingI (ShowsPrecSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sing :: Sing (ShowsPrecSym2 d1 d2) Source #

SuppressUnusedWarnings (ShowsPrecSym2 arg6989586621680295060 arg6989586621680295059 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym2 arg6989586621680295060 arg6989586621680295059 :: TyFun Symbol Symbol -> Type) (arg6989586621680295061 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsPrecSym2 arg6989586621680295060 arg6989586621680295059 :: TyFun Symbol Symbol -> Type) (arg6989586621680295061 :: Symbol) = ShowsPrec arg6989586621680295060 arg6989586621680295059 arg6989586621680295061

type ShowsPrecSym3 (arg6989586621680295059 :: Nat) (arg6989586621680295060 :: a6989586621680294621) (arg6989586621680295061 :: Symbol) = ShowsPrec arg6989586621680295059 arg6989586621680295060 arg6989586621680295061 Source #

data Show_Sym0 :: forall a6989586621680294621. (~>) a6989586621680294621 Symbol Source #

Instances

Instances details
SShow a => SingI (Show_Sym0 :: TyFun a Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (Show_Sym0 :: TyFun a6989586621680294621 Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (arg6989586621680295065 :: a) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (Show_Sym0 :: TyFun a Symbol -> Type) (arg6989586621680295065 :: a) = Show_ arg6989586621680295065

type Show_Sym1 (arg6989586621680295065 :: a6989586621680294621) = Show_ arg6989586621680295065 Source #

data ShowListSym0 :: forall a6989586621680294621. (~>) [a6989586621680294621] ((~>) Symbol Symbol) Source #

Instances

Instances details
SShow a => SingI (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowListSym0 :: TyFun [a6989586621680294621] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListSym0 :: TyFun [a6989586621680294621] (Symbol ~> Symbol) -> Type) (arg6989586621680295067 :: [a6989586621680294621]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListSym0 :: TyFun [a6989586621680294621] (Symbol ~> Symbol) -> Type) (arg6989586621680295067 :: [a6989586621680294621]) = ShowListSym1 arg6989586621680295067

data ShowListSym1 (arg6989586621680295067 :: [a6989586621680294621]) :: (~>) Symbol Symbol Source #

Instances

Instances details
(SShow a, SingI d) => SingI (ShowListSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sing :: Sing (ShowListSym1 d) Source #

SuppressUnusedWarnings (ShowListSym1 arg6989586621680295067 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListSym1 arg6989586621680295067 :: TyFun Symbol Symbol -> Type) (arg6989586621680295068 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListSym1 arg6989586621680295067 :: TyFun Symbol Symbol -> Type) (arg6989586621680295068 :: Symbol) = ShowList arg6989586621680295067 arg6989586621680295068

type ShowListSym2 (arg6989586621680295067 :: [a6989586621680294621]) (arg6989586621680295068 :: Symbol) = ShowList arg6989586621680295067 arg6989586621680295068 Source #

data ShowsSym0 :: forall a6989586621680294606. (~>) a6989586621680294606 ((~>) Symbol Symbol) Source #

Instances

Instances details
SShow a => SingI (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowsSym0 :: TyFun a6989586621680294606 (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsSym0 :: TyFun a6989586621680294606 (Symbol ~> Symbol) -> Type) (a6989586621680295051 :: a6989586621680294606) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsSym0 :: TyFun a6989586621680294606 (Symbol ~> Symbol) -> Type) (a6989586621680295051 :: a6989586621680294606) = ShowsSym1 a6989586621680295051

data ShowsSym1 (a6989586621680295051 :: a6989586621680294606) :: (~>) Symbol Symbol Source #

Instances

Instances details
(SShow a, SingI d) => SingI (ShowsSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sing :: Sing (ShowsSym1 d) Source #

SuppressUnusedWarnings (ShowsSym1 a6989586621680295051 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsSym1 a6989586621680295051 :: TyFun Symbol Symbol -> Type) (a6989586621680295052 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowsSym1 a6989586621680295051 :: TyFun Symbol Symbol -> Type) (a6989586621680295052 :: Symbol) = Shows a6989586621680295051 a6989586621680295052

type ShowsSym2 (a6989586621680295051 :: a6989586621680294606) (a6989586621680295052 :: Symbol) = Shows a6989586621680295051 a6989586621680295052 Source #

data ShowListWithSym0 :: forall a6989586621680294605. (~>) ((~>) a6989586621680294605 ((~>) Symbol Symbol)) ((~>) [a6989586621680294605] ((~>) Symbol Symbol)) Source #

Instances

Instances details
SingI (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowListWithSym0 :: TyFun (a6989586621680294605 ~> (Symbol ~> Symbol)) ([a6989586621680294605] ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListWithSym0 :: TyFun (a6989586621680294605 ~> (Symbol ~> Symbol)) ([a6989586621680294605] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680295031 :: a6989586621680294605 ~> (Symbol ~> Symbol)) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListWithSym0 :: TyFun (a6989586621680294605 ~> (Symbol ~> Symbol)) ([a6989586621680294605] ~> (Symbol ~> Symbol)) -> Type) (a6989586621680295031 :: a6989586621680294605 ~> (Symbol ~> Symbol)) = ShowListWithSym1 a6989586621680295031

data ShowListWithSym1 (a6989586621680295031 :: (~>) a6989586621680294605 ((~>) Symbol Symbol)) :: (~>) [a6989586621680294605] ((~>) Symbol Symbol) Source #

Instances

Instances details
SingI d => SingI (ShowListWithSym1 d :: TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowListWithSym1 a6989586621680295031 :: TyFun [a6989586621680294605] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListWithSym1 a6989586621680295031 :: TyFun [a6989586621680294605] (Symbol ~> Symbol) -> Type) (a6989586621680295032 :: [a6989586621680294605]) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListWithSym1 a6989586621680295031 :: TyFun [a6989586621680294605] (Symbol ~> Symbol) -> Type) (a6989586621680295032 :: [a6989586621680294605]) = ShowListWithSym2 a6989586621680295031 a6989586621680295032

data ShowListWithSym2 (a6989586621680295031 :: (~>) a6989586621680294605 ((~>) Symbol Symbol)) (a6989586621680295032 :: [a6989586621680294605]) :: (~>) Symbol Symbol Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI (ShowListWithSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sing :: Sing (ShowListWithSym2 d1 d2) Source #

SuppressUnusedWarnings (ShowListWithSym2 a6989586621680295032 a6989586621680295031 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListWithSym2 a6989586621680295032 a6989586621680295031 :: TyFun Symbol Symbol -> Type) (a6989586621680295033 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowListWithSym2 a6989586621680295032 a6989586621680295031 :: TyFun Symbol Symbol -> Type) (a6989586621680295033 :: Symbol) = ShowListWith a6989586621680295032 a6989586621680295031 a6989586621680295033

type ShowListWithSym3 (a6989586621680295031 :: (~>) a6989586621680294605 ((~>) Symbol Symbol)) (a6989586621680295032 :: [a6989586621680294605]) (a6989586621680295033 :: Symbol) = ShowListWith a6989586621680295031 a6989586621680295032 a6989586621680295033 Source #

data ShowCharSym0 :: (~>) Symbol ((~>) Symbol Symbol) Source #

Instances

Instances details
SingI ShowCharSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ShowCharSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowCharSym0 (a6989586621680295025 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowCharSym0 (a6989586621680295025 :: Symbol) = ShowCharSym1 a6989586621680295025

data ShowCharSym1 (a6989586621680295025 :: Symbol) :: (~>) Symbol Symbol Source #

Instances

Instances details
SingI d => SingI (ShowCharSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sing :: Sing (ShowCharSym1 d) Source #

SuppressUnusedWarnings (ShowCharSym1 a6989586621680295025 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowCharSym1 a6989586621680295025 :: TyFun Symbol Symbol -> Type) (a6989586621680295026 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowCharSym1 a6989586621680295025 :: TyFun Symbol Symbol -> Type) (a6989586621680295026 :: Symbol) = ShowChar a6989586621680295025 a6989586621680295026

type ShowCharSym2 (a6989586621680295025 :: Symbol) (a6989586621680295026 :: Symbol) = ShowChar a6989586621680295025 a6989586621680295026 Source #

data ShowStringSym0 :: (~>) Symbol ((~>) Symbol Symbol) Source #

Instances

Instances details
SingI ShowStringSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ShowStringSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowStringSym0 (a6989586621680295015 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowStringSym0 (a6989586621680295015 :: Symbol) = ShowStringSym1 a6989586621680295015

data ShowStringSym1 (a6989586621680295015 :: Symbol) :: (~>) Symbol Symbol Source #

Instances

Instances details
SingI d => SingI (ShowStringSym1 d :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowStringSym1 a6989586621680295015 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowStringSym1 a6989586621680295015 :: TyFun Symbol Symbol -> Type) (a6989586621680295016 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowStringSym1 a6989586621680295015 :: TyFun Symbol Symbol -> Type) (a6989586621680295016 :: Symbol) = ShowString a6989586621680295015 a6989586621680295016

type ShowStringSym2 (a6989586621680295015 :: Symbol) (a6989586621680295016 :: Symbol) = ShowString a6989586621680295015 a6989586621680295016 Source #

data ShowParenSym0 :: (~>) Bool ((~>) ((~>) Symbol Symbol) ((~>) Symbol Symbol)) Source #

Instances

Instances details
SingI ShowParenSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ShowParenSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowParenSym0 (a6989586621680294997 :: Bool) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowParenSym0 (a6989586621680294997 :: Bool) = ShowParenSym1 a6989586621680294997

data ShowParenSym1 (a6989586621680294997 :: Bool) :: (~>) ((~>) Symbol Symbol) ((~>) Symbol Symbol) Source #

Instances

Instances details
SingI d => SingI (ShowParenSym1 d :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings (ShowParenSym1 a6989586621680294997 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowParenSym1 a6989586621680294997 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680294998 :: Symbol ~> Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowParenSym1 a6989586621680294997 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680294998 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621680294997 a6989586621680294998

data ShowParenSym2 (a6989586621680294997 :: Bool) (a6989586621680294998 :: (~>) Symbol Symbol) :: (~>) Symbol Symbol Source #

Instances

Instances details
(SingI d1, SingI d2) => SingI (ShowParenSym2 d1 d2 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

Methods

sing :: Sing (ShowParenSym2 d1 d2) Source #

SuppressUnusedWarnings (ShowParenSym2 a6989586621680294998 a6989586621680294997 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowParenSym2 a6989586621680294998 a6989586621680294997 :: TyFun Symbol Symbol -> Type) (a6989586621680294999 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply (ShowParenSym2 a6989586621680294998 a6989586621680294997 :: TyFun Symbol Symbol -> Type) (a6989586621680294999 :: Symbol) = ShowParen a6989586621680294998 a6989586621680294997 a6989586621680294999

data ShowSpaceSym0 :: (~>) Symbol Symbol Source #

Instances

Instances details
SingI ShowSpaceSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ShowSpaceSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowSpaceSym0 (a6989586621680294988 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowSpaceSym0 (a6989586621680294988 :: Symbol) = ShowSpace a6989586621680294988

type ShowSpaceSym1 (a6989586621680294988 :: Symbol) = ShowSpace a6989586621680294988 Source #

data ShowCommaSpaceSym0 :: (~>) Symbol Symbol Source #

Instances

Instances details
SingI ShowCommaSpaceSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

SuppressUnusedWarnings ShowCommaSpaceSym0 Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowCommaSpaceSym0 (a6989586621680294983 :: Symbol) Source # 
Instance details

Defined in Data.Singletons.Prelude.Show

type Apply ShowCommaSpaceSym0 (a6989586621680294983 :: Symbol) = ShowCommaSpace a6989586621680294983

type ShowCommaSpaceSym1 (a6989586621680294983 :: Symbol) = ShowCommaSpace a6989586621680294983 Source #