singletons-2.4.1: A framework for generating singleton types

Copyright(C) 2017 Ryan Scott
LicenseBSD-style (see LICENSE)
MaintainerRichard Eisenberg (rae@cs.brynmawr.edu)
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Singletons.ShowSing

Contents

Description

Defines the class ShowSing, allowing for conversion of Sing values to readable Strings.

Synopsis

The ShowSing class

class ShowSing k where Source #

Members of the ShowSing kind class can have their Sing values converted to Strings in a fashion similar to that of the Show class. (In fact, this class only exists because one cannot write Show instances for Sings of the form instance (forall z. Show (Sing (z :: k))) => Show (Sing (x :: [k])).)

This class should not be confused with the promoted or singled versions of Show from Data.Singletons.Prelude.Show (PShow and SShow, respectively). The output of ShowSing is intended to reflect the singleton type, whereas the output of PShow and SShow reflects the original type. That is, showing SFalse with ShowSing would yield "SFalse", whereas PShow and SShow would yield "False".

Instances of this class are generated alongside singleton definitions for datatypes that derive a Show instance. Moreover, having a ShowSing instances makes it simple to define a Show instance. For instance:

instance ShowSing a => ShowSing [a] where
  showsSingPrec = ...
instance ShowSing a => Show (Sing (x :: [a])) where
  showsPrec = showsSingPrec

As a result, singleton definitions for datatypes that derive a Show instance also get a Show instance for the singleton type as well (in addition to promoted and singled Show instances).

To recap: singletons will give you all of these for a datatype that derives a Show instance:

  • A promoted (PShow) instance
  • A singled (SShow) instance
  • A ShowSing instance for the singleton type
  • A Show instance for the singleton type

What a bargain!

Minimal complete definition

showsSingPrec

Methods

showsSingPrec :: Int -> Sing (a :: k) -> ShowS Source #

showsSingPrec p s convert a Sing value p to a readable String with precedence p.

Instances
ShowSing Bool Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a -> ShowS Source #

ShowSing Ordering Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a -> ShowS Source #

ShowSing Type Source # 
Instance details

Defined in Data.Singletons.TypeRepStar

Methods

showsSingPrec :: Int -> Sing a -> ShowS Source #

ShowSing Nat Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a -> ShowS Source #

ShowSing Symbol Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a -> ShowS Source #

ShowSing () Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a -> ShowS Source #

ShowSing Void Source # 
Instance details

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

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

Defined in Data.Singletons.ShowSing

Methods

showsSingPrec :: Int -> Sing a0 -> ShowS Source #

Orphan instances

Show (SSymbol s) Source # 
Instance details

Methods

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

show :: SSymbol s -> String #

showList :: [SSymbol s] -> ShowS #

Show (SNat n) Source # 
Instance details

Methods

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

show :: SNat n -> String #

showList :: [SNat n] -> ShowS #

Show (Sing z) Source # 
Instance details

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

Show (Sing z) Source # 
Instance details

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

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

Methods

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

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #