singletons-base-3.3: A promoted and singled version of the base library
Copyright(C) 2017 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRyan Scott
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageGHC2021

Text.Show.Singletons

Description

Defines the SShow singleton version of the Show type class.

Synopsis

Documentation

class PShow a Source #

Associated Types

type ShowsPrec (arg :: Natural) (arg1 :: a) (arg2 :: Symbol) :: Symbol Source #

type ShowsPrec (arg :: Natural) (arg1 :: a) (arg2 :: Symbol) = Apply (Apply (Apply (ShowsPrec_6989586621680208728Sym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) arg) arg1) arg2

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

type Show_ (arg :: a) = Apply (Show__6989586621680208740Sym0 :: TyFun a Symbol -> Type) arg

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

type ShowList (arg :: [a]) (arg1 :: Symbol) = Apply (Apply (ShowList_6989586621680208748Sym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) arg) arg1

Instances

Instances details
PShow All Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type ShowsPrec a1 (a2 :: All) a3 
Instance details

Defined in Data.Semigroup.Singletons

type ShowsPrec a1 (a2 :: All) a3
type Show_ (arg :: All) 
Instance details

Defined in Data.Semigroup.Singletons

type Show_ (arg :: All)
type ShowList (arg :: [All]) arg1 
Instance details

Defined in Data.Semigroup.Singletons

type ShowList (arg :: [All]) arg1
PShow Any Source # 
Instance details

Defined in Data.Semigroup.Singletons

Associated Types

type ShowsPrec a1 (a2 :: Any) a3 
Instance details

Defined in Data.Semigroup.Singletons

type ShowsPrec a1 (a2 :: Any) a3
type Show_ (arg :: Any) 
Instance details

Defined in Data.Semigroup.Singletons

type Show_ (arg :: Any)
type ShowList (arg :: [Any]) arg1 
Instance details

Defined in Data.Semigroup.Singletons

type ShowList (arg :: [Any]) arg1
PShow Void Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec a1 (a2 :: Void) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: Void) a3
type Show_ (arg :: Void) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Void)
type ShowList (arg1 :: [Void]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Void]) arg2
PShow Ordering Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec a1 (a2 :: Ordering) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: Ordering) a3
type Show_ (arg :: Ordering) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Ordering)
type ShowList (arg1 :: [Ordering]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Ordering]) arg2
PShow Natural Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec _1 (n :: Natural) x 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec _1 (n :: Natural) x
type Show_ (arg :: Natural) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Natural)
type ShowList (arg1 :: [Natural]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Natural]) arg2
PShow () Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec a1 (a2 :: ()) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: ()) a3
type Show_ (arg :: ()) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: ())
type ShowList (arg1 :: [()]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [()]) arg2
PShow Bool Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec a1 (a2 :: Bool) a3 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec a1 (a2 :: Bool) a3
type Show_ (arg :: Bool) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Bool)
type ShowList (arg1 :: [Bool]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Bool]) arg2
PShow Char Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec p (c :: Char) x 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec p (c :: Char) x
type Show_ (arg :: Char) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Char)
type ShowList (cs :: [Char]) x 
Instance details

Defined in Text.Show.Singletons

type ShowList (cs :: [Char]) x
PShow Symbol Source # 
Instance details

Defined in Text.Show.Singletons

Associated Types

type ShowsPrec _1 (s :: Symbol) x 
Instance details

Defined in Text.Show.Singletons

type ShowsPrec _1 (s :: Symbol) x
type Show_ (arg :: Symbol) 
Instance details

Defined in Text.Show.Singletons

type Show_ (arg :: Symbol)
type ShowList (arg1 :: [Symbol]) arg2 
Instance details

Defined in Text.Show.Singletons

type ShowList (arg1 :: [Symbol]) arg2
PShow (Identity a) Source # 
Instance details

Defined in Data.Functor.Identity.Singletons

PShow (First a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PShow (Last a) Source # 
Instance details

Defined in Data.Monoid.Singletons

PShow (First a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Last a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Max a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Min a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (WrappedMonoid m) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Dual a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Product a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (Sum a) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (NonEmpty a) Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Maybe a) Source # 
Instance details

Defined in Text.Show.Singletons

PShow [a] Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Either a b) Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

PShow (Arg a b) Source # 
Instance details

Defined in Data.Semigroup.Singletons

PShow (a, b) Source # 
Instance details

Defined in Text.Show.Singletons

PShow (Const a b) Source # 
Instance details

Defined in Data.Functor.Const.Singletons

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

class SShow a where Source #

Minimal complete definition

Nothing

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

default sShowsPrec :: forall (t1 :: Natural) (t2 :: a) (t3 :: Symbol). Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3 ~ Apply (Apply (Apply (ShowsPrec_6989586621680208728Sym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3 => Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

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

sShowList :: forall (t1 :: [a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

default sShowList :: forall (t1 :: [a]) (t2 :: Symbol). Apply (Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) t1) t2 ~ Apply (Apply (ShowList_6989586621680208748Sym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) t1) t2 => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

Instances

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: All) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (All ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [All]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [All] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow Bool => SShow Any Source # 
Instance details

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Any) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Any ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Any]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Any] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow Void Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Void) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Void ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Void]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Void] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow Ordering Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Ordering) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Ordering ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Ordering]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Ordering] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow Natural Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Natural) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Natural ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Natural]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Natural] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow () Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: ()) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (() ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [()]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [()] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow Bool Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Bool) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Bool ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Bool]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Bool] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow Char Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Char) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Char ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Char]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Char] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow Symbol Source # 
Instance details

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Symbol) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Symbol ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Symbol]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Symbol] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Functor.Identity.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Identity a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Identity a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Identity a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Identity a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Monoid.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: First a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (First a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [First a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Monoid.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Last a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Last a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Last a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: First a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (First a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [First a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [First a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Last a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Last a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Last a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Last a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Max a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Max a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Max a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Max a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Min a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Min a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Min a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Min a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: WrappedMonoid m) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (WrappedMonoid m ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [WrappedMonoid m]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [WrappedMonoid m] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Dual a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Dual a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Dual a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Dual a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Product a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Product a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Product a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Product a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Sum a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Sum a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Sum a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Sum a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: NonEmpty a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (NonEmpty a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [NonEmpty a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [NonEmpty a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Maybe a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Maybe a ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Maybe a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Maybe a] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: [a]) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ([a] ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [[a]]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [[a]] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Either a b) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Either a b ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Either a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Either a b] (Symbol ~> Symbol) -> Type) t1) t2) Source #

SShow (Proxy s) Source # 
Instance details

Defined in Data.Proxy.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Proxy s) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Proxy s ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

sShow_ :: forall (t :: Proxy s). Sing t -> Sing (Apply (Show_Sym0 :: TyFun (Proxy s) Symbol -> Type) t) Source #

sShowList :: forall (t1 :: [Proxy s]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Proxy s] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Semigroup.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Arg a b) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Arg a b ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Arg a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Arg a b] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [(a, b)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b)] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Data.Functor.Const.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: Const a b) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (Const a b ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [Const a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [Const a b] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [(a, b, c)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c)] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c, d)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c, d) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [(a, b, c, d)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c, d)] (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Defined in Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c, d, e)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c, d, e) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [(a, b, c, d, e)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c, d, e)] (Symbol ~> Symbol) -> Type) t1) t2) 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 Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c, d, e, f)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c, d, e, f) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [(a, b, c, d, e, f)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c, d, e, f)] (Symbol ~> Symbol) -> Type) t1) t2) 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 Text.Show.Singletons

Methods

sShowsPrec :: forall (t1 :: Natural) (t2 :: (a, b, c, d, e, f, g)) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural ((a, b, c, d, e, f, g) ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

sShowList :: forall (t1 :: [(a, b, c, d, e, f, g)]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowListSym0 :: TyFun [(a, b, c, d, e, f, g)] (Symbol ~> Symbol) -> Type) t1) t2) 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.

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 (a1 :: a) (a2 :: Symbol) :: Symbol where ... Source #

Equations

Shows (s :: k1) a_6989586621680208701 = Apply (Apply (Apply (ShowsPrecSym0 :: TyFun Natural (k1 ~> (Symbol ~> Symbol)) -> Type) (FromInteger 0 :: Natural)) s) a_6989586621680208701 

sShows :: forall a (t1 :: a) (t2 :: Symbol). SShow a => Sing t1 -> Sing t2 -> Sing (Apply (Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) t1) t2) Source #

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

Equations

ShowListWith (_1 :: a ~> (Symbol ~> Symbol)) ('[] :: [a]) s = Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) "[]") s 
ShowListWith (showx :: k ~> (Symbol ~> Symbol)) (x ': xs :: [k]) s = Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) "[") (Apply (Apply showx x) (Apply (Let6989586621680208696ShowlSym4 showx x xs s) xs)) 

sShowListWith :: forall a (t1 :: a ~> (Symbol ~> Symbol)) (t2 :: [a]) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) t1) t2) t3) Source #

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

Equations

ShowChar a_6989586621680208673 a_6989586621680208675 = Apply (Apply ConsSymbolSym0 a_6989586621680208673) a_6989586621680208675 

sShowChar :: forall (t1 :: Char) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowCharSym0 t1) t2) Source #

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

Equations

ShowString a_6989586621680208662 a_6989586621680208664 = Apply (Apply ((<>@#@$) :: TyFun Symbol (Symbol ~> Symbol) -> Type) a_6989586621680208662) a_6989586621680208664 

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

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

Equations

ShowParen b p a_6989586621680208647 = Apply (Case_6989586621680208659 b p a_6989586621680208647 b) a_6989586621680208647 

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

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

Equations

ShowSpace a_6989586621680208637 = Apply (Apply (Lambda_6989586621680208643Sym0 :: TyFun Symbol (TyFun Symbol Symbol -> Type) -> Type) a_6989586621680208637) a_6989586621680208637 

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

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

Equations

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

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

Equations

AppPrec = FromInteger 10 :: Natural 

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

Equations

AppPrec1 = FromInteger 11 :: Natural 

Defunctionalization symbols

data ShowsPrecSym0 (a1 :: TyFun Natural (a ~> (Symbol ~> Symbol))) Source #

Instances

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

Defined in Text.Show.Singletons

SuppressUnusedWarnings (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208714 :: Natural) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym0 :: TyFun Natural (a ~> (Symbol ~> Symbol)) -> Type) (a6989586621680208714 :: Natural) = ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type

data ShowsPrecSym1 (a6989586621680208714 :: Natural) (b :: TyFun a (Symbol ~> Symbol)) Source #

Instances

Instances details
SShow a => SingI1 (ShowsPrecSym1 :: Natural -> TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Natural). Sing x -> Sing (ShowsPrecSym1 x :: TyFun a (Symbol ~> Symbol) -> Type) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym1 d :: TyFun a (Symbol ~> Symbol) -> Type) #

SuppressUnusedWarnings (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym1 a6989586621680208714 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208715 :: a) = ShowsPrecSym2 a6989586621680208714 a6989586621680208715

data ShowsPrecSym2 (a6989586621680208714 :: Natural) (a6989586621680208715 :: a) (c :: TyFun Symbol Symbol) Source #

Instances

Instances details
SShow a => SingI2 (ShowsPrecSym2 :: Natural -> a -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Natural) (y :: a). Sing x -> Sing y -> Sing (ShowsPrecSym2 x y) #

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

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsPrecSym2 d x) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsPrecSym2 d1 d2) #

SuppressUnusedWarnings (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) (a6989586621680208716 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsPrecSym2 a6989586621680208714 a6989586621680208715 :: TyFun Symbol Symbol -> Type) (a6989586621680208716 :: Symbol) = ShowsPrec a6989586621680208714 a6989586621680208715 a6989586621680208716

type family ShowsPrecSym3 (a6989586621680208714 :: Natural) (a6989586621680208715 :: a) (a6989586621680208716 :: Symbol) :: Symbol where ... Source #

Equations

ShowsPrecSym3 a6989586621680208714 (a6989586621680208715 :: a) a6989586621680208716 = ShowsPrec a6989586621680208714 a6989586621680208715 a6989586621680208716 

data Show_Sym0 (a1 :: TyFun a Symbol) Source #

Instances

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (Show_Sym0 :: TyFun a Symbol -> Type) #

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

type family Show_Sym1 (a6989586621680208719 :: a) :: Symbol where ... Source #

Equations

Show_Sym1 (a6989586621680208719 :: a) = Show_ a6989586621680208719 

data ShowListSym0 (a1 :: TyFun [a] (Symbol ~> Symbol)) Source #

Instances

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym0 :: TyFun [a] (Symbol ~> Symbol) -> Type) #

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

data ShowListSym1 (a6989586621680208723 :: [a]) (b :: TyFun Symbol Symbol) Source #

Instances

Instances details
SShow a => SingI1 (ShowListSym1 :: [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListSym1 x) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListSym1 d) #

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

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) (a6989586621680208724 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListSym1 a6989586621680208723 :: TyFun Symbol Symbol -> Type) (a6989586621680208724 :: Symbol) = ShowList a6989586621680208723 a6989586621680208724

type family ShowListSym2 (a6989586621680208723 :: [a]) (a6989586621680208724 :: Symbol) :: Symbol where ... Source #

Equations

ShowListSym2 (a6989586621680208723 :: [a]) a6989586621680208724 = ShowList a6989586621680208723 a6989586621680208724 

data ShowsSym0 (a1 :: TyFun a (Symbol ~> Symbol)) Source #

Instances

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) #

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

type Apply (ShowsSym0 :: TyFun a (Symbol ~> Symbol) -> Type) (a6989586621680208706 :: a) = ShowsSym1 a6989586621680208706

data ShowsSym1 (a6989586621680208706 :: a) (b :: TyFun Symbol Symbol) Source #

Instances

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

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a). Sing x -> Sing (ShowsSym1 x) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowsSym1 d) #

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

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) (a6989586621680208707 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowsSym1 a6989586621680208706 :: TyFun Symbol Symbol -> Type) (a6989586621680208707 :: Symbol) = Shows a6989586621680208706 a6989586621680208707

type family ShowsSym2 (a6989586621680208706 :: a) (a6989586621680208707 :: Symbol) :: Symbol where ... Source #

Equations

ShowsSym2 (a6989586621680208706 :: a) a6989586621680208707 = Shows a6989586621680208706 a6989586621680208707 

data ShowListWithSym0 (a1 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol))) Source #

Instances

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym0 :: TyFun (a ~> (Symbol ~> Symbol)) ([a] ~> (Symbol ~> Symbol)) -> Type) #

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

data ShowListWithSym1 (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) (b :: TyFun [a] (Symbol ~> Symbol)) Source #

Instances

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym1 d) #

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

Defined in Text.Show.Singletons

SingI1 (ShowListWithSym1 :: (a ~> (Symbol ~> Symbol)) -> TyFun [a] (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: a ~> (Symbol ~> Symbol)). Sing x -> Sing (ShowListWithSym1 x) #

type Apply (ShowListWithSym1 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208689 :: [a]) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym1 a6989586621680208688 :: TyFun [a] (Symbol ~> Symbol) -> Type) (a6989586621680208689 :: [a]) = ShowListWithSym2 a6989586621680208688 a6989586621680208689

data ShowListWithSym2 (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) (a6989586621680208689 :: [a]) (c :: TyFun Symbol Symbol) Source #

Instances

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

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: [a]). Sing x -> Sing (ShowListWithSym2 d x) #

SingI2 (ShowListWithSym2 :: (a ~> (Symbol ~> Symbol)) -> [a] -> TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: a ~> (Symbol ~> Symbol)) (y :: [a]). Sing x -> Sing y -> Sing (ShowListWithSym2 x y) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowListWithSym2 d1 d2) #

SuppressUnusedWarnings (ShowListWithSym2 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym2 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) (a6989586621680208690 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowListWithSym2 a6989586621680208688 a6989586621680208689 :: TyFun Symbol Symbol -> Type) (a6989586621680208690 :: Symbol) = ShowListWith a6989586621680208688 a6989586621680208689 a6989586621680208690

type family ShowListWithSym3 (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) (a6989586621680208689 :: [a]) (a6989586621680208690 :: Symbol) :: Symbol where ... Source #

Equations

ShowListWithSym3 (a6989586621680208688 :: a ~> (Symbol ~> Symbol)) (a6989586621680208689 :: [a]) a6989586621680208690 = ShowListWith a6989586621680208688 a6989586621680208689 a6989586621680208690 

data ShowCharSym0 (a :: TyFun Char (Symbol ~> Symbol)) Source #

Instances

Instances details
SingI ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowCharSym0 Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621680208680 :: Char) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply ShowCharSym0 (a6989586621680208680 :: Char) = ShowCharSym1 a6989586621680208680

data ShowCharSym1 (a6989586621680208680 :: Char) (b :: TyFun Symbol Symbol) Source #

Instances

Instances details
SingI1 ShowCharSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Char). Sing x -> Sing (ShowCharSym1 x) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowCharSym1 d) #

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

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) (a6989586621680208681 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowCharSym1 a6989586621680208680 :: TyFun Symbol Symbol -> Type) (a6989586621680208681 :: Symbol) = ShowChar a6989586621680208680 a6989586621680208681

type family ShowCharSym2 (a6989586621680208680 :: Char) (a6989586621680208681 :: Symbol) :: Symbol where ... Source #

Equations

ShowCharSym2 a6989586621680208680 a6989586621680208681 = ShowChar a6989586621680208680 a6989586621680208681 

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

Instances

Instances details
SingI ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowStringSym0 Source # 
Instance details

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

data ShowStringSym1 (a6989586621680208669 :: Symbol) (b :: TyFun Symbol Symbol) Source #

Instances

Instances details
SingI1 ShowStringSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol). Sing x -> Sing (ShowStringSym1 x) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowStringSym1 d) #

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

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621680208669 :: TyFun Symbol Symbol -> Type) (a6989586621680208670 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowStringSym1 a6989586621680208669 :: TyFun Symbol Symbol -> Type) (a6989586621680208670 :: Symbol) = ShowString a6989586621680208669 a6989586621680208670

type family ShowStringSym2 (a6989586621680208669 :: Symbol) (a6989586621680208670 :: Symbol) :: Symbol where ... Source #

Equations

ShowStringSym2 a6989586621680208669 a6989586621680208670 = ShowString a6989586621680208669 a6989586621680208670 

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

Instances

Instances details
SingI ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowParenSym0 Source # 
Instance details

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

data ShowParenSym1 (a6989586621680208653 :: Bool) (b :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol)) Source #

Instances

Instances details
SingI1 ShowParenSym1 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Bool). Sing x -> Sing (ShowParenSym1 x) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym1 d) #

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

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

type Apply (ShowParenSym1 a6989586621680208653 :: TyFun (Symbol ~> Symbol) (Symbol ~> Symbol) -> Type) (a6989586621680208654 :: Symbol ~> Symbol) = ShowParenSym2 a6989586621680208653 a6989586621680208654

data ShowParenSym2 (a6989586621680208653 :: Bool) (a6989586621680208654 :: Symbol ~> Symbol) (c :: TyFun Symbol Symbol) Source #

Instances

Instances details
SingI2 ShowParenSym2 Source # 
Instance details

Defined in Text.Show.Singletons

Methods

liftSing2 :: forall (x :: Bool) (y :: Symbol ~> Symbol). Sing x -> Sing y -> Sing (ShowParenSym2 x y) #

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

Defined in Text.Show.Singletons

Methods

sing :: Sing (ShowParenSym2 d1 d2) #

SuppressUnusedWarnings (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) Source # 
Instance details

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

Methods

liftSing :: forall (x :: Symbol ~> Symbol). Sing x -> Sing (ShowParenSym2 d x) #

type Apply (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) (a6989586621680208655 :: Symbol) Source # 
Instance details

Defined in Text.Show.Singletons

type Apply (ShowParenSym2 a6989586621680208653 a6989586621680208654 :: TyFun Symbol Symbol -> Type) (a6989586621680208655 :: Symbol) = ShowParen a6989586621680208653 a6989586621680208654 a6989586621680208655

data ShowSpaceSym0 (a :: TyFun Symbol Symbol) Source #

Instances

Instances details
SingI ShowSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

type family ShowSpaceSym1 (a6989586621680208641 :: Symbol) :: Symbol where ... Source #

Equations

ShowSpaceSym1 a6989586621680208641 = ShowSpace a6989586621680208641 

data ShowCommaSpaceSym0 (a :: TyFun Symbol Symbol) Source #

Instances

Instances details
SingI ShowCommaSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

SuppressUnusedWarnings ShowCommaSpaceSym0 Source # 
Instance details

Defined in Text.Show.Singletons

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

Defined in Text.Show.Singletons

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

type family ShowCommaSpaceSym1 (a6989586621680208635 :: Symbol) :: Symbol where ... Source #

Equations

ShowCommaSpaceSym1 a6989586621680208635 = ShowCommaSpace a6989586621680208635 

type family AppPrecSym0 :: Natural where ... Source #

Equations

AppPrecSym0 = AppPrec 

type family AppPrec1Sym0 :: Natural where ... Source #

Equations

AppPrec1Sym0 = AppPrec1