generic-deriving-1.13: Generic programming library for generalised deriving.

Safe HaskellTrustworthy
LanguageHaskell2010

Generics.Deriving.Show

Contents

Synopsis

Generic show class

class GShow a where Source #

Minimal complete definition

Nothing

Methods

gshowsPrec :: Int -> a -> ShowS Source #

gshowsPrec :: (Generic a, GShow' (Rep a)) => Int -> a -> ShowS Source #

gshows :: a -> ShowS Source #

gshow :: a -> String Source #

gshowList :: [a] -> ShowS Source #

Instances
GShow Bool Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Char Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Double Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Float Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Int Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Int8 Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Int16 Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Int32 Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Int64 Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Integer Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Natural Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Ordering Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Word Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Word8 Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Word16 Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Word32 Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Word64 Source # 
Instance details

Defined in Generics.Deriving.Show

GShow () Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> () -> ShowS Source #

gshows :: () -> ShowS Source #

gshow :: () -> String Source #

gshowList :: [()] -> ShowS Source #

GShow Handle Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Void Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Version Source # 
Instance details

Defined in Generics.Deriving.Show

GShow HandlePosn Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Fd Source # 
Instance details

Defined in Generics.Deriving.Show

GShow ExitCode Source # 
Instance details

Defined in Generics.Deriving.Show

GShow IOErrorType Source # 
Instance details

Defined in Generics.Deriving.Show

GShow BufferMode Source # 
Instance details

Defined in Generics.Deriving.Show

GShow SeekMode Source # 
Instance details

Defined in Generics.Deriving.Show

GShow IOError Source # 
Instance details

Defined in Generics.Deriving.Show

GShow All Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Any Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Fixity Source # 
Instance details

Defined in Generics.Deriving.Show

GShow Associativity Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CChar Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CSChar Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CUChar Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CShort Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CUShort Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CInt Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CUInt Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CLong Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CULong Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CLLong Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CULLong Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CBool Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CFloat Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CDouble Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CPtrdiff Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CSize Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CWchar Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CSigAtomic Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CClock Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CTime Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CUSeconds Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CSUSeconds Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CIntPtr Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CUIntPtr Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CIntMax Source # 
Instance details

Defined in Generics.Deriving.Show

GShow CUIntMax Source # 
Instance details

Defined in Generics.Deriving.Show

GShow WordPtr Source # 
Instance details

Defined in Generics.Deriving.Show

GShow IntPtr Source # 
Instance details

Defined in Generics.Deriving.Show

GShow IOMode Source # 
Instance details

Defined in Generics.Deriving.Show

GShow GeneralCategory Source # 
Instance details

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> [a] -> ShowS Source #

gshows :: [a] -> ShowS Source #

gshow :: [a] -> String Source #

gshowList :: [[a]] -> ShowS Source #

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

Defined in Generics.Deriving.Show

GShow (Ptr a) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow (FunPtr a) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow p => GShow (Par1 p) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow (ForeignPtr a) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow a => GShow (Complex a) Source # 
Instance details

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

GShow a => GShow (Option a) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow a => GShow (ZipList a) Source # 
Instance details

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

GShow a => GShow (NonEmpty a) Source # 
Instance details

Defined in Generics.Deriving.Show

(Generic a, GShow' (Rep a)) => GShow (Default a) Source #

For example, with this type:

newtype TestShow = TestShow Bool
  deriving (GShow) via (Default Bool)

gshow for TestShow would produce the same string as gshow for Bool.

In this example, TestShow requires no Generic instance, as the constraint on gshowsPrec from Default Bool is Generic Bool.

In general, when using a newtype wrapper, the instance can be derived via the wrapped type, as here (via Default Bool rather than Default TestShow).

Instance details

Defined in Generics.Deriving.Default

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

Defined in Generics.Deriving.Show

GShow (U1 p) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> U1 p -> ShowS Source #

gshows :: U1 p -> ShowS Source #

gshow :: U1 p -> String Source #

gshowList :: [U1 p] -> ShowS Source #

GShow (UChar p) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow (UDouble p) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow (UFloat p) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow (UInt p) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow (UWord p) Source # 
Instance details

Defined in Generics.Deriving.Show

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (a, b) -> ShowS Source #

gshows :: (a, b) -> ShowS Source #

gshow :: (a, b) -> String Source #

gshowList :: [(a, b)] -> ShowS Source #

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> Arg a b -> ShowS Source #

gshows :: Arg a b -> ShowS Source #

gshow :: Arg a b -> String Source #

gshowList :: [Arg a b] -> ShowS Source #

GShow (Proxy s) Source # 
Instance details

Defined in Generics.Deriving.Show

GShow (f p) => GShow (Rec1 f p) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> Rec1 f p -> ShowS Source #

gshows :: Rec1 f p -> ShowS Source #

gshow :: Rec1 f p -> String Source #

gshowList :: [Rec1 f p] -> ShowS Source #

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (a, b, c) -> ShowS Source #

gshows :: (a, b, c) -> ShowS Source #

gshow :: (a, b, c) -> String Source #

gshowList :: [(a, b, c)] -> ShowS Source #

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> Const a b -> ShowS Source #

gshows :: Const a b -> ShowS Source #

gshow :: Const a b -> String Source #

gshowList :: [Const a b] -> ShowS Source #

GShow (f a) => GShow (Alt f a) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> Alt f a -> ShowS Source #

gshows :: Alt f a -> ShowS Source #

gshow :: Alt f a -> String Source #

gshowList :: [Alt f a] -> ShowS Source #

GShow c => GShow (K1 i c p) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> K1 i c p -> ShowS Source #

gshows :: K1 i c p -> ShowS Source #

gshow :: K1 i c p -> String Source #

gshowList :: [K1 i c p] -> ShowS Source #

(GShow (f p), GShow (g p)) => GShow ((f :+: g) p) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (f :+: g) p -> ShowS Source #

gshows :: (f :+: g) p -> ShowS Source #

gshow :: (f :+: g) p -> String Source #

gshowList :: [(f :+: g) p] -> ShowS Source #

(GShow (f p), GShow (g p)) => GShow ((f :*: g) p) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (f :*: g) p -> ShowS Source #

gshows :: (f :*: g) p -> ShowS Source #

gshow :: (f :*: g) p -> String Source #

gshowList :: [(f :*: g) p] -> ShowS Source #

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (a, b, c, d) -> ShowS Source #

gshows :: (a, b, c, d) -> ShowS Source #

gshow :: (a, b, c, d) -> String Source #

gshowList :: [(a, b, c, d)] -> ShowS Source #

GShow (f p) => GShow (M1 i c f p) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> M1 i c f p -> ShowS Source #

gshows :: M1 i c f p -> ShowS Source #

gshow :: M1 i c f p -> String Source #

gshowList :: [M1 i c f p] -> ShowS Source #

GShow (f (g p)) => GShow ((f :.: g) p) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (f :.: g) p -> ShowS Source #

gshows :: (f :.: g) p -> ShowS Source #

gshow :: (f :.: g) p -> String Source #

gshowList :: [(f :.: g) p] -> ShowS Source #

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (a, b, c, d, e) -> ShowS Source #

gshows :: (a, b, c, d, e) -> ShowS Source #

gshow :: (a, b, c, d, e) -> String Source #

gshowList :: [(a, b, c, d, e)] -> ShowS Source #

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (a, b, c, d, e, f) -> ShowS Source #

gshows :: (a, b, c, d, e, f) -> ShowS Source #

gshow :: (a, b, c, d, e, f) -> String Source #

gshowList :: [(a, b, c, d, e, f)] -> ShowS Source #

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

Defined in Generics.Deriving.Show

Methods

gshowsPrec :: Int -> (a, b, c, d, e, f, g) -> ShowS Source #

gshows :: (a, b, c, d, e, f, g) -> ShowS Source #

gshow :: (a, b, c, d, e, f, g) -> String Source #

gshowList :: [(a, b, c, d, e, f, g)] -> ShowS Source #

Default definition

Internal show class

class GShow' f where Source #

Minimal complete definition

gshowsPrec'

Methods

gshowsPrec' :: Type -> Int -> f a -> ShowS Source #

isNullary :: f a -> Bool Source #

Instances
GShow' (V1 :: Type -> Type) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type0 -> Int -> V1 a -> ShowS Source #

isNullary :: V1 a -> Bool Source #

GShow' (U1 :: Type -> Type) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type0 -> Int -> U1 a -> ShowS Source #

isNullary :: U1 a -> Bool Source #

GShow' (UChar :: Type -> Type) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type0 -> Int -> UChar a -> ShowS Source #

isNullary :: UChar a -> Bool Source #

GShow' (UDouble :: Type -> Type) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type0 -> Int -> UDouble a -> ShowS Source #

isNullary :: UDouble a -> Bool Source #

GShow' (UFloat :: Type -> Type) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type0 -> Int -> UFloat a -> ShowS Source #

isNullary :: UFloat a -> Bool Source #

GShow' (UInt :: Type -> Type) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type0 -> Int -> UInt a -> ShowS Source #

isNullary :: UInt a -> Bool Source #

GShow' (UWord :: Type -> Type) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type0 -> Int -> UWord a -> ShowS Source #

isNullary :: UWord a -> Bool Source #

GShow c => GShow' (K1 i c :: Type -> Type) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type0 -> Int -> K1 i c a -> ShowS Source #

isNullary :: K1 i c a -> Bool Source #

(GShow' a, GShow' b) => GShow' (a :+: b) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type -> Int -> (a :+: b) a0 -> ShowS Source #

isNullary :: (a :+: b) a0 -> Bool Source #

(GShow' a, GShow' b) => GShow' (a :*: b) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type -> Int -> (a :*: b) a0 -> ShowS Source #

isNullary :: (a :*: b) a0 -> Bool Source #

GShow' a => GShow' (M1 D d a) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type -> Int -> M1 D d a a0 -> ShowS Source #

isNullary :: M1 D d a a0 -> Bool Source #

(GShow' a, Constructor c) => GShow' (M1 C c a) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type -> Int -> M1 C c a a0 -> ShowS Source #

isNullary :: M1 C c a a0 -> Bool Source #

(Selector s, GShow' a) => GShow' (M1 S s a) Source # 
Instance details

Defined in Generics.Deriving.Show

Methods

gshowsPrec' :: Type -> Int -> M1 S s a a0 -> ShowS Source #

isNullary :: M1 S s a a0 -> Bool Source #