text-show-3.7.2: Efficient conversion of values into Text

Copyright(C) 2014-2017 Ryan Scott
LicenseBSD-style (see the file LICENSE)
MaintainerRyan Scott
StabilityProvisional
PortabilityGHC
Safe HaskellNone
LanguageHaskell2010

TextShow

Contents

Description

Efficiently convert from values to Text via Builders.

Since: 2

Synopsis

The TextShow classes

TextShow

class TextShow a where Source #

Conversion of values to Text. Because there are both strict and lazy Text variants, the TextShow class deliberately avoids using Text in its functions. Instead, showbPrec, showb, and showbList all return Builder, an efficient intermediate form that can be converted to either kind of Text.

Builder is a Monoid, so it is useful to use the mappend (or <>) function to combine Builders when creating TextShow instances. As an example:

import Data.Monoid
import TextShow

data Example = Example Int Int
instance TextShow Example where
    showb (Example i1 i2) = showb i1 <> showbSpace <> showb i2

If you do not want to create TextShow instances manually, you can alternatively use the TextShow.TH module to automatically generate default TextShow instances using Template Haskell, or the TextShow.Generic module to quickly define TextShow instances using genericShowbPrec.

Since: 2

Minimal complete definition

showbPrec | showb

Methods

showbPrec Source #

Arguments

:: Int

The operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10.

-> a

The value to be converted to a Builder.

-> Builder 

Convert a value to a Builder with the given predence.

Since: 2

showb Source #

Arguments

:: a

The value to be converted to a Builder.

-> Builder 

Converts a value to a strict Text. If you hand-define this, it should satisfy:

showb = showbPrec 0

Since: 2

showbList Source #

Arguments

:: [a]

The list of values to be converted to a Builder.

-> Builder 

Converts a list of values to a Builder. By default, this is defined as 'showbList = showbListWith showb, but it can be overridden to allow for specialized displaying of lists (e.g., lists of Chars).

Since: 2

showtPrec Source #

Arguments

:: Int

The operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10.

-> a

The value to be converted to a strict Text.

-> Text 

Converts a value to a strict Text with the given precedence. This can be overridden for efficiency, but it should satisfy:

showtPrec p = toStrict . showtlPrec p

Since: 3

showt Source #

Arguments

:: a

The value to be converted to a strict Text.

-> Text 

Converts a value to a strict Text. This can be overridden for efficiency, but it should satisfy:

showt = showtPrec 0
showt = toStrict . showtl

The first equation is the default definition of showt.

Since: 3

showtList Source #

Arguments

:: [a]

The list of values to be converted to a strict Text.

-> Text 

Converts a list of values to a strict Text. This can be overridden for efficiency, but it should satisfy:

showtList = toStrict . showtlList

Since: 3

showtlPrec Source #

Arguments

:: Int

The operator precedence of the enclosing context (a number from 0 to 11). Function application has precedence 10.

-> a

The value to be converted to a lazy Text.

-> Text 

Converts a value to a lazy Text with the given precedence. This can be overridden for efficiency, but it should satisfy:

showtlPrec p = toLazyText . showbPrec p

Since: 3

showtl Source #

Arguments

:: a

The value to be converted to a lazy Text.

-> Text 

Converts a value to a lazy Text. This can be overridden for efficiency, but it should satisfy:

showtl = showtlPrec 0
showtl = toLazyText . showb

The first equation is the default definition of showtl.

Since: 3

showtlList Source #

Arguments

:: [a]

The list of values to be converted to a lazy Text.

-> Text 

Converts a list of values to a lazy Text. This can be overridden for efficiency, but it should satisfy:

showtlList = toLazyText . showbList

Since: 3

Instances

TextShow ConType Source # 
TextShow a => TextShow (FromTextShow a) Source # 
Show a => TextShow (FromStringShow a) Source # 
(TextShow1 f, TextShow a) => TextShow (FromTextShow1 * f a) Source # 
(Show1 f, Show a) => TextShow (FromStringShow1 * f a) Source #

Not available if using transformers-0.4

(TextShow2 f, TextShow a, TextShow b) => TextShow (FromTextShow2 * * f a b) Source # 
(Show2 f, Show a, Show b) => TextShow (FromStringShow2 * * f a b) Source #

Not available if using transformers-0.4

showbParen :: Bool -> Builder -> Builder Source #

Surrounds Builder output with parentheses if the Bool parameter is True.

Since: 2

showtParen :: Bool -> Text -> Text Source #

Surrounds strict Text output with parentheses if the Bool parameter is True.

Since: 3.4

showtlParen :: Bool -> Text -> Text Source #

Surrounds lazy Text output with parentheses if the Bool parameter is True.

Since: 3.4

showbCommaSpace :: Builder Source #

Construct a Builder containing a comma followed by a space.

Since: 3.6

showtCommaSpace :: Text Source #

Construct a strict Text containing a comma followed by a space.

Since: 3.6

showtlCommaSpace :: Text Source #

Construct a lazy Text containing a comma followed by a space.

Since: 3.6

showbSpace :: Builder Source #

Construct a Builder containing a single space character.

Since: 2

showtSpace :: Text Source #

Construct a strict Text containing a single space character.

Since: 3.4

showtlSpace :: Text Source #

Construct a lazy Text containing a single space character.

Since: 3.4

TextShow1

class TextShow1 f where Source #

Lifting of the TextShow class to unary type constructors.

Since: 2

Minimal complete definition

liftShowbPrec

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder Source #

showbPrec function for an application of the type constructor based on showbPrec and showbList functions for the argument type.

Since: 3

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [f a] -> Builder Source #

showbList function for an application of the type constructor based on showbPrec and showbList functions for the argument type. The default implementation using standard list syntax is correct for most types.

Since: 3

Instances

TextShow1 FromTextShow Source # 

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow a] -> Builder Source #

TextShow1 FromStringShow Source # 

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow a] -> Builder Source #

TextShow1 f => TextShow1 (FromTextShow1 * f) Source # 

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow1 * f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow1 * f a] -> Builder Source #

Show1 f => TextShow1 (FromStringShow1 * f) Source #

Not available if using transformers-0.4

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow1 * f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow1 * f a] -> Builder Source #

(TextShow2 f, TextShow a) => TextShow1 (FromTextShow2 * * f a) Source # 

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow2 * * f a a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow2 * * f a a] -> Builder Source #

(Show2 f, Show a) => TextShow1 (FromStringShow2 * * f a) Source #

Not available if using transformers-0.4

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow2 * * f a a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow2 * * f a a] -> Builder Source #

showbPrec1 :: (TextShow1 f, TextShow a) => Int -> f a -> Builder Source #

Lift the standard showbPrec and showbList functions through the type constructor.

Since: 2

showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder Source #

showbUnaryWith sp n p x produces the Builder representation of a unary data constructor with name n and argument x, in precedence context p, using the function sp to show occurrences of the type argument.

Since: 2

liftShowtPrec :: TextShow1 f => (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text Source #

showtPrec function for an application of the type constructor based on showtPrec and showtList functions for the argument type.

The current implementation is based on liftShowbPrec internally.

Since: 3.4

liftShowtlPrec :: TextShow1 f => (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text Source #

showtlPrec function for an application of the type constructor based on showtlPrec and showtlList functions for the argument type.

The current implementation is based on liftShowbPrec internally.

Since: 3.4

TextShow2

class TextShow2 f where Source #

Lifting of the TextShow class to binary type constructors.

Since: 2

Minimal complete definition

liftShowbPrec2

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> f a b -> Builder Source #

showbPrec function for an application of the type constructor based on showbPrec and showbList functions for the argument types.

Since: 3

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [f a b] -> Builder Source #

showbList function for an application of the type constructor based on showbPrec and showbList functions for the argument types. The default implementation using standard list syntax is correct for most types.

Since: 3

Instances

TextShow2 f => TextShow2 (FromTextShow2 * * f) Source # 

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> FromTextShow2 * * f a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [FromTextShow2 * * f a b] -> Builder Source #

Show2 f => TextShow2 (FromStringShow2 * * f) Source #

Not available if using transformers-0.4

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> FromStringShow2 * * f a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [FromStringShow2 * * f a b] -> Builder Source #

showbPrec2 :: (TextShow2 f, TextShow a, TextShow b) => Int -> f a b -> Builder Source #

Lift two showbPrec functions through the type constructor.

Since: 2

showbBinaryWith :: (Int -> a -> Builder) -> (Int -> b -> Builder) -> Builder -> Int -> a -> b -> Builder Source #

showbBinaryWith sp n p x y produces the Builder representation of a binary data constructor with name n and arguments x and y, in precedence context p, using the functions sp1 and sp2 to show occurrences of the type arguments.

Since: 2

liftShowtPrec2 :: TextShow2 f => (Int -> a -> Text) -> ([a] -> Text) -> (Int -> b -> Text) -> ([b] -> Text) -> Int -> f a b -> Text Source #

showtPrec function for an application of the type constructor based on showtPrec and showtList functions for the argument type.

The current implementation is based on liftShowbPrec2 internally.

Since: 3.4

liftShowtlPrec2 :: TextShow2 f => (Int -> a -> Text) -> ([a] -> Text) -> (Int -> b -> Text) -> ([b] -> Text) -> Int -> f a b -> Text Source #

showtlPrec function for an application of the type constructor based on showtlPrec and showtlList functions for the argument type.

The current implementation is based on liftShowbPrec2 internally.

Since: 3.4

Builders

The Builder type

data Builder :: * #

A Builder is an efficient way to build lazy Text values. There are several functions for constructing builders, but only one to inspect them: to extract any data, you have to turn them into lazy Text values using toLazyText.

Internally, a builder constructs a lazy Text by filling arrays piece by piece. As each buffer is filled, it is 'popped' off, to become a new chunk of the resulting lazy Text. All this is hidden from the user of the Builder.

toText :: Builder -> Text Source #

Convert a Builder to a strict Text.

Since: 2

toLazyText :: Builder -> Text #

O(n). Extract a lazy Text from a Builder with a default buffer size. The construction work takes place if and when the relevant part of the lazy Text is demanded.

toLazyTextWith :: Int -> Builder -> Text #

O(n). Extract a lazy Text from a Builder, using the given size for the initial buffer. The construction work takes place if and when the relevant part of the lazy Text is demanded.

If the initial buffer is too small to hold all data, subsequent buffers will be the default buffer size.

toString :: Builder -> String Source #

Convert a Builder to a String (without surrounding it with double quotes, as show would).

Since: 2

Constructing Builders

singleton :: Char -> Builder #

O(1). A Builder taking a single character, satisfying

fromText :: Text -> Builder #

O(1). A Builder taking a Text, satisfying

fromLazyText :: Text -> Builder #

O(1). A Builder taking a lazy Text, satisfying

fromString :: String -> Builder #

O(1). A Builder taking a String, satisfying

Flushing the buffer state

flush :: Builder #

O(1). Pop the strict Text we have constructed so far, if any, yielding a new chunk in the result lazy Text.

Builder utility functions

lengthB :: Builder -> Int64 Source #

Computes the length of a Builder.

Since: 2

unlinesB :: [Builder] -> Builder Source #

Merges several Builders, separating them by newlines.

Since: 2

unwordsB :: [Builder] -> Builder Source #

Merges several Builders, separating them by spaces.

Since: 2

Printing values

printT :: TextShow a => a -> IO () Source #

Writes a value's strict Text representation to the standard output, followed by a newline.

Since: 2

printTL :: TextShow a => a -> IO () Source #

Writes a value's lazy Text representation to the standard output, followed by a newline.

Since: 2

hPrintT :: TextShow a => Handle -> a -> IO () Source #

Writes a value's strict Text representation to a file handle, followed by a newline.

Since: 2

hPrintTL :: TextShow a => Handle -> a -> IO () Source #

Writes a value's lazy Text representation to a file handle, followed by a newline.

Since: 2

Conversions

Conversion between TextShow and string Show

newtype FromStringShow a Source #

The TextShow instance for FromStringShow is based on its String Show instance. That is,

showbPrec p (FromStringShow x) = showsToShowb showsPrec p x

Since: 2

Constructors

FromStringShow 

Fields

Instances

Functor FromStringShow Source # 

Methods

fmap :: (a -> b) -> FromStringShow a -> FromStringShow b #

(<$) :: a -> FromStringShow b -> FromStringShow a #

Foldable FromStringShow Source # 

Methods

fold :: Monoid m => FromStringShow m -> m #

foldMap :: Monoid m => (a -> m) -> FromStringShow a -> m #

foldr :: (a -> b -> b) -> b -> FromStringShow a -> b #

foldr' :: (a -> b -> b) -> b -> FromStringShow a -> b #

foldl :: (b -> a -> b) -> b -> FromStringShow a -> b #

foldl' :: (b -> a -> b) -> b -> FromStringShow a -> b #

foldr1 :: (a -> a -> a) -> FromStringShow a -> a #

foldl1 :: (a -> a -> a) -> FromStringShow a -> a #

toList :: FromStringShow a -> [a] #

null :: FromStringShow a -> Bool #

length :: FromStringShow a -> Int #

elem :: Eq a => a -> FromStringShow a -> Bool #

maximum :: Ord a => FromStringShow a -> a #

minimum :: Ord a => FromStringShow a -> a #

sum :: Num a => FromStringShow a -> a #

product :: Num a => FromStringShow a -> a #

Traversable FromStringShow Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FromStringShow a -> f (FromStringShow b) #

sequenceA :: Applicative f => FromStringShow (f a) -> f (FromStringShow a) #

mapM :: Monad m => (a -> m b) -> FromStringShow a -> m (FromStringShow b) #

sequence :: Monad m => FromStringShow (m a) -> m (FromStringShow a) #

Show1 FromStringShow Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromStringShow a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromStringShow a] -> ShowS #

TextShow1 FromStringShow Source # 

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow a] -> Builder Source #

Eq a => Eq (FromStringShow a) Source # 
Data a => Data (FromStringShow a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromStringShow a -> c (FromStringShow a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromStringShow a) #

toConstr :: FromStringShow a -> Constr #

dataTypeOf :: FromStringShow a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FromStringShow a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromStringShow a)) #

gmapT :: (forall b. Data b => b -> b) -> FromStringShow a -> FromStringShow a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromStringShow a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromStringShow a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromStringShow a -> m (FromStringShow a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow a -> m (FromStringShow a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow a -> m (FromStringShow a) #

Ord a => Ord (FromStringShow a) Source # 
Read a => Read (FromStringShow a) Source # 
Show a => Show (FromStringShow a) Source # 
Generic (FromStringShow a) Source # 

Associated Types

type Rep (FromStringShow a) :: * -> * #

Lift a => Lift (FromStringShow a) Source # 

Methods

lift :: FromStringShow a -> Q Exp #

Show a => TextShow (FromStringShow a) Source # 
Generic1 * FromStringShow Source # 

Associated Types

type Rep1 FromStringShow (f :: FromStringShow -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 FromStringShow f a #

to1 :: Rep1 FromStringShow f a -> f a #

type Rep (FromStringShow a) Source # 
type Rep (FromStringShow a) = D1 * (MetaData "FromStringShow" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 * (MetaCons "FromStringShow" PrefixI True) (S1 * (MetaSel (Just Symbol "fromStringShow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))
type Rep1 * FromStringShow Source # 
type Rep1 * FromStringShow = D1 * (MetaData "FromStringShow" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 * (MetaCons "FromStringShow" PrefixI True) (S1 * (MetaSel (Just Symbol "fromStringShow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype FromTextShow a Source #

The String Show instance for FromTextShow is based on its TextShow instance. That is,

showsPrec p (FromTextShow x) = showbToShows showbPrec p x

Since: 2

Constructors

FromTextShow 

Fields

Instances

Functor FromTextShow Source # 

Methods

fmap :: (a -> b) -> FromTextShow a -> FromTextShow b #

(<$) :: a -> FromTextShow b -> FromTextShow a #

Foldable FromTextShow Source # 

Methods

fold :: Monoid m => FromTextShow m -> m #

foldMap :: Monoid m => (a -> m) -> FromTextShow a -> m #

foldr :: (a -> b -> b) -> b -> FromTextShow a -> b #

foldr' :: (a -> b -> b) -> b -> FromTextShow a -> b #

foldl :: (b -> a -> b) -> b -> FromTextShow a -> b #

foldl' :: (b -> a -> b) -> b -> FromTextShow a -> b #

foldr1 :: (a -> a -> a) -> FromTextShow a -> a #

foldl1 :: (a -> a -> a) -> FromTextShow a -> a #

toList :: FromTextShow a -> [a] #

null :: FromTextShow a -> Bool #

length :: FromTextShow a -> Int #

elem :: Eq a => a -> FromTextShow a -> Bool #

maximum :: Ord a => FromTextShow a -> a #

minimum :: Ord a => FromTextShow a -> a #

sum :: Num a => FromTextShow a -> a #

product :: Num a => FromTextShow a -> a #

Traversable FromTextShow Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FromTextShow a -> f (FromTextShow b) #

sequenceA :: Applicative f => FromTextShow (f a) -> f (FromTextShow a) #

mapM :: Monad m => (a -> m b) -> FromTextShow a -> m (FromTextShow b) #

sequence :: Monad m => FromTextShow (m a) -> m (FromTextShow a) #

Show1 FromTextShow Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromTextShow a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromTextShow a] -> ShowS #

TextShow1 FromTextShow Source # 

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow a] -> Builder Source #

Eq a => Eq (FromTextShow a) Source # 
Data a => Data (FromTextShow a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromTextShow a -> c (FromTextShow a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromTextShow a) #

toConstr :: FromTextShow a -> Constr #

dataTypeOf :: FromTextShow a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FromTextShow a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromTextShow a)) #

gmapT :: (forall b. Data b => b -> b) -> FromTextShow a -> FromTextShow a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromTextShow a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromTextShow a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromTextShow a -> m (FromTextShow a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow a -> m (FromTextShow a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow a -> m (FromTextShow a) #

Ord a => Ord (FromTextShow a) Source # 
Read a => Read (FromTextShow a) Source # 
TextShow a => Show (FromTextShow a) Source # 
Generic (FromTextShow a) Source # 

Associated Types

type Rep (FromTextShow a) :: * -> * #

Methods

from :: FromTextShow a -> Rep (FromTextShow a) x #

to :: Rep (FromTextShow a) x -> FromTextShow a #

Lift a => Lift (FromTextShow a) Source # 

Methods

lift :: FromTextShow a -> Q Exp #

TextShow a => TextShow (FromTextShow a) Source # 
Generic1 * FromTextShow Source # 

Associated Types

type Rep1 FromTextShow (f :: FromTextShow -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 FromTextShow f a #

to1 :: Rep1 FromTextShow f a -> f a #

type Rep (FromTextShow a) Source # 
type Rep (FromTextShow a) = D1 * (MetaData "FromTextShow" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 * (MetaCons "FromTextShow" PrefixI True) (S1 * (MetaSel (Just Symbol "fromTextShow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)))
type Rep1 * FromTextShow Source # 
type Rep1 * FromTextShow = D1 * (MetaData "FromTextShow" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 * (MetaCons "FromTextShow" PrefixI True) (S1 * (MetaSel (Just Symbol "fromTextShow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

newtype FromStringShow1 f a Source #

The TextShow1 instance for FromStringShow1 is based on its String Show1 instance. That is,

liftShowbPrec sp sl p (FromStringShow1 x) =
    showsPrecToShowbPrec (liftShowsPrec (showbPrecToShowsPrec sp)
                                            (showbToShows         sl))
                           p x

Since: 3

Constructors

FromStringShow1 

Fields

Instances

Generic1 k (FromStringShow1 k f) Source # 

Associated Types

type Rep1 (FromStringShow1 k f) (f :: FromStringShow1 k f -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (FromStringShow1 k f) f a #

to1 :: Rep1 (FromStringShow1 k f) f a -> f a #

Functor f => Functor (FromStringShow1 * f) Source # 

Methods

fmap :: (a -> b) -> FromStringShow1 * f a -> FromStringShow1 * f b #

(<$) :: a -> FromStringShow1 * f b -> FromStringShow1 * f a #

Foldable f => Foldable (FromStringShow1 * f) Source # 

Methods

fold :: Monoid m => FromStringShow1 * f m -> m #

foldMap :: Monoid m => (a -> m) -> FromStringShow1 * f a -> m #

foldr :: (a -> b -> b) -> b -> FromStringShow1 * f a -> b #

foldr' :: (a -> b -> b) -> b -> FromStringShow1 * f a -> b #

foldl :: (b -> a -> b) -> b -> FromStringShow1 * f a -> b #

foldl' :: (b -> a -> b) -> b -> FromStringShow1 * f a -> b #

foldr1 :: (a -> a -> a) -> FromStringShow1 * f a -> a #

foldl1 :: (a -> a -> a) -> FromStringShow1 * f a -> a #

toList :: FromStringShow1 * f a -> [a] #

null :: FromStringShow1 * f a -> Bool #

length :: FromStringShow1 * f a -> Int #

elem :: Eq a => a -> FromStringShow1 * f a -> Bool #

maximum :: Ord a => FromStringShow1 * f a -> a #

minimum :: Ord a => FromStringShow1 * f a -> a #

sum :: Num a => FromStringShow1 * f a -> a #

product :: Num a => FromStringShow1 * f a -> a #

Traversable f => Traversable (FromStringShow1 * f) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FromStringShow1 * f a -> f (FromStringShow1 * f b) #

sequenceA :: Applicative f => FromStringShow1 * f (f a) -> f (FromStringShow1 * f a) #

mapM :: Monad m => (a -> m b) -> FromStringShow1 * f a -> m (FromStringShow1 * f b) #

sequence :: Monad m => FromStringShow1 * f (m a) -> m (FromStringShow1 * f a) #

Show1 f => Show1 (FromStringShow1 * f) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromStringShow1 * f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromStringShow1 * f a] -> ShowS #

Show1 f => TextShow1 (FromStringShow1 * f) Source #

Not available if using transformers-0.4

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow1 * f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow1 * f a] -> Builder Source #

Eq (f a) => Eq (FromStringShow1 k f a) Source # 

Methods

(==) :: FromStringShow1 k f a -> FromStringShow1 k f a -> Bool #

(/=) :: FromStringShow1 k f a -> FromStringShow1 k f a -> Bool #

(Data (f a), Typeable * k, Typeable (k -> *) f, Typeable k a) => Data (FromStringShow1 k f a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromStringShow1 k f a -> c (FromStringShow1 k f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromStringShow1 k f a) #

toConstr :: FromStringShow1 k f a -> Constr #

dataTypeOf :: FromStringShow1 k f a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FromStringShow1 k f a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromStringShow1 k f a)) #

gmapT :: (forall b. Data b => b -> b) -> FromStringShow1 k f a -> FromStringShow1 k f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow1 k f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow1 k f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromStringShow1 k f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromStringShow1 k f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromStringShow1 k f a -> m (FromStringShow1 k f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow1 k f a -> m (FromStringShow1 k f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow1 k f a -> m (FromStringShow1 k f a) #

Ord (f a) => Ord (FromStringShow1 k f a) Source # 
Read (f a) => Read (FromStringShow1 k f a) Source # 
(Show1 f, Show a) => Show (FromStringShow1 * f a) Source # 
Generic (FromStringShow1 k f a) Source # 

Associated Types

type Rep (FromStringShow1 k f a) :: * -> * #

Methods

from :: FromStringShow1 k f a -> Rep (FromStringShow1 k f a) x #

to :: Rep (FromStringShow1 k f a) x -> FromStringShow1 k f a #

Lift (f a) => Lift (FromStringShow1 k f a) Source # 

Methods

lift :: FromStringShow1 k f a -> Q Exp #

(Show1 f, Show a) => TextShow (FromStringShow1 * f a) Source #

Not available if using transformers-0.4

type Rep1 k (FromStringShow1 k f) Source # 
type Rep1 k (FromStringShow1 k f) = D1 k (MetaData "FromStringShow1" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 k (MetaCons "FromStringShow1" PrefixI True) (S1 k (MetaSel (Just Symbol "fromStringShow1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 k f)))
type Rep (FromStringShow1 k f a) Source # 
type Rep (FromStringShow1 k f a) = D1 * (MetaData "FromStringShow1" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 * (MetaCons "FromStringShow1" PrefixI True) (S1 * (MetaSel (Just Symbol "fromStringShow1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f a))))

newtype FromTextShow1 f a Source #

The String Show1 instance for FromTextShow1 is based on its TextShow1 instance. That is,

liftShowsPrec sp sl p (FromTextShow1 x) =
    showbPrecToShowsPrec (liftShowbPrec (showsPrecToShowbPrec sp)
                                            (showsToShowb         sl))
                           p x

Since: 3

Constructors

FromTextShow1 

Fields

Instances

Generic1 k (FromTextShow1 k f) Source # 

Associated Types

type Rep1 (FromTextShow1 k f) (f :: FromTextShow1 k f -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (FromTextShow1 k f) f a #

to1 :: Rep1 (FromTextShow1 k f) f a -> f a #

Functor f => Functor (FromTextShow1 * f) Source # 

Methods

fmap :: (a -> b) -> FromTextShow1 * f a -> FromTextShow1 * f b #

(<$) :: a -> FromTextShow1 * f b -> FromTextShow1 * f a #

Foldable f => Foldable (FromTextShow1 * f) Source # 

Methods

fold :: Monoid m => FromTextShow1 * f m -> m #

foldMap :: Monoid m => (a -> m) -> FromTextShow1 * f a -> m #

foldr :: (a -> b -> b) -> b -> FromTextShow1 * f a -> b #

foldr' :: (a -> b -> b) -> b -> FromTextShow1 * f a -> b #

foldl :: (b -> a -> b) -> b -> FromTextShow1 * f a -> b #

foldl' :: (b -> a -> b) -> b -> FromTextShow1 * f a -> b #

foldr1 :: (a -> a -> a) -> FromTextShow1 * f a -> a #

foldl1 :: (a -> a -> a) -> FromTextShow1 * f a -> a #

toList :: FromTextShow1 * f a -> [a] #

null :: FromTextShow1 * f a -> Bool #

length :: FromTextShow1 * f a -> Int #

elem :: Eq a => a -> FromTextShow1 * f a -> Bool #

maximum :: Ord a => FromTextShow1 * f a -> a #

minimum :: Ord a => FromTextShow1 * f a -> a #

sum :: Num a => FromTextShow1 * f a -> a #

product :: Num a => FromTextShow1 * f a -> a #

Traversable f => Traversable (FromTextShow1 * f) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FromTextShow1 * f a -> f (FromTextShow1 * f b) #

sequenceA :: Applicative f => FromTextShow1 * f (f a) -> f (FromTextShow1 * f a) #

mapM :: Monad m => (a -> m b) -> FromTextShow1 * f a -> m (FromTextShow1 * f b) #

sequence :: Monad m => FromTextShow1 * f (m a) -> m (FromTextShow1 * f a) #

TextShow1 f => Show1 (FromTextShow1 * f) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromTextShow1 * f a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromTextShow1 * f a] -> ShowS #

TextShow1 f => TextShow1 (FromTextShow1 * f) Source # 

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow1 * f a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow1 * f a] -> Builder Source #

Eq (f a) => Eq (FromTextShow1 k f a) Source # 

Methods

(==) :: FromTextShow1 k f a -> FromTextShow1 k f a -> Bool #

(/=) :: FromTextShow1 k f a -> FromTextShow1 k f a -> Bool #

(Data (f a), Typeable * k, Typeable (k -> *) f, Typeable k a) => Data (FromTextShow1 k f a) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FromTextShow1 k f a -> c (FromTextShow1 k f a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromTextShow1 k f a) #

toConstr :: FromTextShow1 k f a -> Constr #

dataTypeOf :: FromTextShow1 k f a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FromTextShow1 k f a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromTextShow1 k f a)) #

gmapT :: (forall b. Data b => b -> b) -> FromTextShow1 k f a -> FromTextShow1 k f a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow1 k f a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow1 k f a -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromTextShow1 k f a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromTextShow1 k f a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromTextShow1 k f a -> m (FromTextShow1 k f a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow1 k f a -> m (FromTextShow1 k f a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow1 k f a -> m (FromTextShow1 k f a) #

Ord (f a) => Ord (FromTextShow1 k f a) Source # 

Methods

compare :: FromTextShow1 k f a -> FromTextShow1 k f a -> Ordering #

(<) :: FromTextShow1 k f a -> FromTextShow1 k f a -> Bool #

(<=) :: FromTextShow1 k f a -> FromTextShow1 k f a -> Bool #

(>) :: FromTextShow1 k f a -> FromTextShow1 k f a -> Bool #

(>=) :: FromTextShow1 k f a -> FromTextShow1 k f a -> Bool #

max :: FromTextShow1 k f a -> FromTextShow1 k f a -> FromTextShow1 k f a #

min :: FromTextShow1 k f a -> FromTextShow1 k f a -> FromTextShow1 k f a #

Read (f a) => Read (FromTextShow1 k f a) Source # 
(TextShow1 f, TextShow a) => Show (FromTextShow1 * f a) Source #

Not available if using transformers-0.4

Generic (FromTextShow1 k f a) Source # 

Associated Types

type Rep (FromTextShow1 k f a) :: * -> * #

Methods

from :: FromTextShow1 k f a -> Rep (FromTextShow1 k f a) x #

to :: Rep (FromTextShow1 k f a) x -> FromTextShow1 k f a #

Lift (f a) => Lift (FromTextShow1 k f a) Source # 

Methods

lift :: FromTextShow1 k f a -> Q Exp #

(TextShow1 f, TextShow a) => TextShow (FromTextShow1 * f a) Source # 
type Rep1 k (FromTextShow1 k f) Source # 
type Rep1 k (FromTextShow1 k f) = D1 k (MetaData "FromTextShow1" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 k (MetaCons "FromTextShow1" PrefixI True) (S1 k (MetaSel (Just Symbol "fromTextShow1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 k f)))
type Rep (FromTextShow1 k f a) Source # 
type Rep (FromTextShow1 k f a) = D1 * (MetaData "FromTextShow1" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 * (MetaCons "FromTextShow1" PrefixI True) (S1 * (MetaSel (Just Symbol "fromTextShow1") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f a))))

newtype FromStringShow2 f a b Source #

The TextShow2 instance for FromStringShow2 is based on its String Show2 instance. That is,

liftShowbPrec2 sp1 sl1 sp2 sl2 p (FromStringShow2 x) =
    showsPrecToShowbPrec (liftShowsPrec2 (showbPrecToShowsPrec sp1)
                                             (showbToShows         sl1)
                                             (showbPrecToShowsPrec sp2)
                                             (showbToShows         sl2))
                           p x

Since: 3

Constructors

FromStringShow2 

Fields

Instances

Generic1 k1 (FromStringShow2 k2 k1 f a) Source # 

Associated Types

type Rep1 (FromStringShow2 k2 k1 f a) (f :: FromStringShow2 k2 k1 f a -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (FromStringShow2 k2 k1 f a) f a #

to1 :: Rep1 (FromStringShow2 k2 k1 f a) f a -> f a #

Bitraversable f => Bitraversable (FromStringShow2 * * f) Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> FromStringShow2 * * f a b -> f (FromStringShow2 * * f c d) #

Bifoldable f => Bifoldable (FromStringShow2 * * f) Source # 

Methods

bifold :: Monoid m => FromStringShow2 * * f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> FromStringShow2 * * f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> FromStringShow2 * * f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> FromStringShow2 * * f a b -> c #

Bifunctor f => Bifunctor (FromStringShow2 * * f) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> FromStringShow2 * * f a c -> FromStringShow2 * * f b d #

first :: (a -> b) -> FromStringShow2 * * f a c -> FromStringShow2 * * f b c #

second :: (b -> c) -> FromStringShow2 * * f a b -> FromStringShow2 * * f a c #

Show2 f => Show2 (FromStringShow2 * * f) Source #

Not available if using transformers-0.4

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> FromStringShow2 * * f a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [FromStringShow2 * * f a b] -> ShowS #

Show2 f => TextShow2 (FromStringShow2 * * f) Source #

Not available if using transformers-0.4

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> FromStringShow2 * * f a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [FromStringShow2 * * f a b] -> Builder Source #

Functor (f a) => Functor (FromStringShow2 k * f a) Source # 

Methods

fmap :: (a -> b) -> FromStringShow2 k * f a a -> FromStringShow2 k * f a b #

(<$) :: a -> FromStringShow2 k * f a b -> FromStringShow2 k * f a a #

Foldable (f a) => Foldable (FromStringShow2 k * f a) Source # 

Methods

fold :: Monoid m => FromStringShow2 k * f a m -> m #

foldMap :: Monoid m => (a -> m) -> FromStringShow2 k * f a a -> m #

foldr :: (a -> b -> b) -> b -> FromStringShow2 k * f a a -> b #

foldr' :: (a -> b -> b) -> b -> FromStringShow2 k * f a a -> b #

foldl :: (b -> a -> b) -> b -> FromStringShow2 k * f a a -> b #

foldl' :: (b -> a -> b) -> b -> FromStringShow2 k * f a a -> b #

foldr1 :: (a -> a -> a) -> FromStringShow2 k * f a a -> a #

foldl1 :: (a -> a -> a) -> FromStringShow2 k * f a a -> a #

toList :: FromStringShow2 k * f a a -> [a] #

null :: FromStringShow2 k * f a a -> Bool #

length :: FromStringShow2 k * f a a -> Int #

elem :: Eq a => a -> FromStringShow2 k * f a a -> Bool #

maximum :: Ord a => FromStringShow2 k * f a a -> a #

minimum :: Ord a => FromStringShow2 k * f a a -> a #

sum :: Num a => FromStringShow2 k * f a a -> a #

product :: Num a => FromStringShow2 k * f a a -> a #

Traversable (f a) => Traversable (FromStringShow2 k * f a) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FromStringShow2 k * f a a -> f (FromStringShow2 k * f a b) #

sequenceA :: Applicative f => FromStringShow2 k * f a (f a) -> f (FromStringShow2 k * f a a) #

mapM :: Monad m => (a -> m b) -> FromStringShow2 k * f a a -> m (FromStringShow2 k * f a b) #

sequence :: Monad m => FromStringShow2 k * f a (m a) -> m (FromStringShow2 k * f a a) #

(Show2 f, Show a) => Show1 (FromStringShow2 * * f a) Source #

Not available if using transformers-0.4

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromStringShow2 * * f a a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromStringShow2 * * f a a] -> ShowS #

(Show2 f, Show a) => TextShow1 (FromStringShow2 * * f a) Source #

Not available if using transformers-0.4

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromStringShow2 * * f a a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromStringShow2 * * f a a] -> Builder Source #

Eq (f a b) => Eq (FromStringShow2 k1 k2 f a b) Source # 

Methods

(==) :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> Bool #

(/=) :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> Bool #

(Data (f a b), Typeable * k2, Typeable * k1, Typeable (k1 -> k2 -> *) f, Typeable k2 b, Typeable k1 a) => Data (FromStringShow2 k1 k2 f a b) Source # 

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> FromStringShow2 k1 k2 f a b -> c (FromStringShow2 k1 k2 f a b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromStringShow2 k1 k2 f a b) #

toConstr :: FromStringShow2 k1 k2 f a b -> Constr #

dataTypeOf :: FromStringShow2 k1 k2 f a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FromStringShow2 k1 k2 f a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromStringShow2 k1 k2 f a b)) #

gmapT :: (forall c. Data c => c -> c) -> FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow2 k1 k2 f a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow2 k1 k2 f a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromStringShow2 k1 k2 f a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromStringShow2 k1 k2 f a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromStringShow2 k1 k2 f a b -> m (FromStringShow2 k1 k2 f a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow2 k1 k2 f a b -> m (FromStringShow2 k1 k2 f a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow2 k1 k2 f a b -> m (FromStringShow2 k1 k2 f a b) #

Ord (f a b) => Ord (FromStringShow2 k1 k2 f a b) Source # 

Methods

compare :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> Ordering #

(<) :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> Bool #

(<=) :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> Bool #

(>) :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> Bool #

(>=) :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> Bool #

max :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b #

min :: FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b -> FromStringShow2 k1 k2 f a b #

Read (f a b) => Read (FromStringShow2 k1 k2 f a b) Source # 

Methods

readsPrec :: Int -> ReadS (FromStringShow2 k1 k2 f a b) #

readList :: ReadS [FromStringShow2 k1 k2 f a b] #

readPrec :: ReadPrec (FromStringShow2 k1 k2 f a b) #

readListPrec :: ReadPrec [FromStringShow2 k1 k2 f a b] #

(Show2 f, Show a, Show b) => Show (FromStringShow2 * * f a b) Source #

Not available if using transformers-0.4

Methods

showsPrec :: Int -> FromStringShow2 * * f a b -> ShowS #

show :: FromStringShow2 * * f a b -> String #

showList :: [FromStringShow2 * * f a b] -> ShowS #

Generic (FromStringShow2 k1 k2 f a b) Source # 

Associated Types

type Rep (FromStringShow2 k1 k2 f a b) :: * -> * #

Methods

from :: FromStringShow2 k1 k2 f a b -> Rep (FromStringShow2 k1 k2 f a b) x #

to :: Rep (FromStringShow2 k1 k2 f a b) x -> FromStringShow2 k1 k2 f a b #

Lift (f a b) => Lift (FromStringShow2 k1 k2 f a b) Source # 

Methods

lift :: FromStringShow2 k1 k2 f a b -> Q Exp #

(Show2 f, Show a, Show b) => TextShow (FromStringShow2 * * f a b) Source #

Not available if using transformers-0.4

type Rep1 k1 (FromStringShow2 k2 k1 f a) Source # 
type Rep1 k1 (FromStringShow2 k2 k1 f a) = D1 k1 (MetaData "FromStringShow2" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 k1 (MetaCons "FromStringShow2" PrefixI True) (S1 k1 (MetaSel (Just Symbol "fromStringShow2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 k1 (f a))))
type Rep (FromStringShow2 k1 k2 f a b) Source # 
type Rep (FromStringShow2 k1 k2 f a b) = D1 * (MetaData "FromStringShow2" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 * (MetaCons "FromStringShow2" PrefixI True) (S1 * (MetaSel (Just Symbol "fromStringShow2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f a b))))

newtype FromTextShow2 f a b Source #

The String Show2 instance for FromTextShow2 is based on its TextShow2 instance. That is,

liftShowsPrec2 sp1 sl1 sp2 sl2 p (FromTextShow2 x) =
    showbPrecToShowsPrec (liftShowbPrec2 (showsPrecToShowbPrec sp1)
                                             (showsToShowb         sl1)
                                             (showsPrecToShowbPrec sp2)
                                             (showsToShowb         sl2))
                           p x

Since: 3

Constructors

FromTextShow2 

Fields

Instances

Generic1 k1 (FromTextShow2 k2 k1 f a) Source # 

Associated Types

type Rep1 (FromTextShow2 k2 k1 f a) (f :: FromTextShow2 k2 k1 f a -> *) :: k -> * #

Methods

from1 :: f a -> Rep1 (FromTextShow2 k2 k1 f a) f a #

to1 :: Rep1 (FromTextShow2 k2 k1 f a) f a -> f a #

Bitraversable f => Bitraversable (FromTextShow2 * * f) Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> FromTextShow2 * * f a b -> f (FromTextShow2 * * f c d) #

Bifoldable f => Bifoldable (FromTextShow2 * * f) Source # 

Methods

bifold :: Monoid m => FromTextShow2 * * f m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> FromTextShow2 * * f a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> FromTextShow2 * * f a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> FromTextShow2 * * f a b -> c #

Bifunctor f => Bifunctor (FromTextShow2 * * f) Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> FromTextShow2 * * f a c -> FromTextShow2 * * f b d #

first :: (a -> b) -> FromTextShow2 * * f a c -> FromTextShow2 * * f b c #

second :: (b -> c) -> FromTextShow2 * * f a b -> FromTextShow2 * * f a c #

TextShow2 f => Show2 (FromTextShow2 * * f) Source #

Not available if using transformers-0.4

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> FromTextShow2 * * f a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [FromTextShow2 * * f a b] -> ShowS #

TextShow2 f => TextShow2 (FromTextShow2 * * f) Source # 

Methods

liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> Int -> FromTextShow2 * * f a b -> Builder Source #

liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder) -> (Int -> b -> Builder) -> ([b] -> Builder) -> [FromTextShow2 * * f a b] -> Builder Source #

Functor (f a) => Functor (FromTextShow2 k * f a) Source # 

Methods

fmap :: (a -> b) -> FromTextShow2 k * f a a -> FromTextShow2 k * f a b #

(<$) :: a -> FromTextShow2 k * f a b -> FromTextShow2 k * f a a #

Foldable (f a) => Foldable (FromTextShow2 k * f a) Source # 

Methods

fold :: Monoid m => FromTextShow2 k * f a m -> m #

foldMap :: Monoid m => (a -> m) -> FromTextShow2 k * f a a -> m #

foldr :: (a -> b -> b) -> b -> FromTextShow2 k * f a a -> b #

foldr' :: (a -> b -> b) -> b -> FromTextShow2 k * f a a -> b #

foldl :: (b -> a -> b) -> b -> FromTextShow2 k * f a a -> b #

foldl' :: (b -> a -> b) -> b -> FromTextShow2 k * f a a -> b #

foldr1 :: (a -> a -> a) -> FromTextShow2 k * f a a -> a #

foldl1 :: (a -> a -> a) -> FromTextShow2 k * f a a -> a #

toList :: FromTextShow2 k * f a a -> [a] #

null :: FromTextShow2 k * f a a -> Bool #

length :: FromTextShow2 k * f a a -> Int #

elem :: Eq a => a -> FromTextShow2 k * f a a -> Bool #

maximum :: Ord a => FromTextShow2 k * f a a -> a #

minimum :: Ord a => FromTextShow2 k * f a a -> a #

sum :: Num a => FromTextShow2 k * f a a -> a #

product :: Num a => FromTextShow2 k * f a a -> a #

Traversable (f a) => Traversable (FromTextShow2 k * f a) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FromTextShow2 k * f a a -> f (FromTextShow2 k * f a b) #

sequenceA :: Applicative f => FromTextShow2 k * f a (f a) -> f (FromTextShow2 k * f a a) #

mapM :: Monad m => (a -> m b) -> FromTextShow2 k * f a a -> m (FromTextShow2 k * f a b) #

sequence :: Monad m => FromTextShow2 k * f a (m a) -> m (FromTextShow2 k * f a a) #

(TextShow2 f, TextShow a) => Show1 (FromTextShow2 * * f a) Source #

Not available if using transformers-0.4

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FromTextShow2 * * f a a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FromTextShow2 * * f a a] -> ShowS #

(TextShow2 f, TextShow a) => TextShow1 (FromTextShow2 * * f a) Source # 

Methods

liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> FromTextShow2 * * f a a -> Builder Source #

liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder) -> [FromTextShow2 * * f a a] -> Builder Source #

Eq (f a b) => Eq (FromTextShow2 k1 k2 f a b) Source # 

Methods

(==) :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> Bool #

(/=) :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> Bool #

(Data (f a b), Typeable * k2, Typeable * k1, Typeable (k1 -> k2 -> *) f, Typeable k2 b, Typeable k1 a) => Data (FromTextShow2 k1 k2 f a b) Source # 

Methods

gfoldl :: (forall d c. Data d => c (d -> c) -> d -> c c) -> (forall g. g -> c g) -> FromTextShow2 k1 k2 f a b -> c (FromTextShow2 k1 k2 f a b) #

gunfold :: (forall c r. Data c => c (c -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromTextShow2 k1 k2 f a b) #

toConstr :: FromTextShow2 k1 k2 f a b -> Constr #

dataTypeOf :: FromTextShow2 k1 k2 f a b -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FromTextShow2 k1 k2 f a b)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromTextShow2 k1 k2 f a b)) #

gmapT :: (forall c. Data c => c -> c) -> FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow2 k1 k2 f a b -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow2 k1 k2 f a b -> r #

gmapQ :: (forall d. Data d => d -> u) -> FromTextShow2 k1 k2 f a b -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FromTextShow2 k1 k2 f a b -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromTextShow2 k1 k2 f a b -> m (FromTextShow2 k1 k2 f a b) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow2 k1 k2 f a b -> m (FromTextShow2 k1 k2 f a b) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow2 k1 k2 f a b -> m (FromTextShow2 k1 k2 f a b) #

Ord (f a b) => Ord (FromTextShow2 k1 k2 f a b) Source # 

Methods

compare :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> Ordering #

(<) :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> Bool #

(<=) :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> Bool #

(>) :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> Bool #

(>=) :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> Bool #

max :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b #

min :: FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b -> FromTextShow2 k1 k2 f a b #

Read (f a b) => Read (FromTextShow2 k1 k2 f a b) Source # 

Methods

readsPrec :: Int -> ReadS (FromTextShow2 k1 k2 f a b) #

readList :: ReadS [FromTextShow2 k1 k2 f a b] #

readPrec :: ReadPrec (FromTextShow2 k1 k2 f a b) #

readListPrec :: ReadPrec [FromTextShow2 k1 k2 f a b] #

(TextShow2 f, TextShow a, TextShow b) => Show (FromTextShow2 * * f a b) Source #

Not available if using transformers-0.4

Methods

showsPrec :: Int -> FromTextShow2 * * f a b -> ShowS #

show :: FromTextShow2 * * f a b -> String #

showList :: [FromTextShow2 * * f a b] -> ShowS #

Generic (FromTextShow2 k1 k2 f a b) Source # 

Associated Types

type Rep (FromTextShow2 k1 k2 f a b) :: * -> * #

Methods

from :: FromTextShow2 k1 k2 f a b -> Rep (FromTextShow2 k1 k2 f a b) x #

to :: Rep (FromTextShow2 k1 k2 f a b) x -> FromTextShow2 k1 k2 f a b #

Lift (f a b) => Lift (FromTextShow2 k1 k2 f a b) Source # 

Methods

lift :: FromTextShow2 k1 k2 f a b -> Q Exp #

(TextShow2 f, TextShow a, TextShow b) => TextShow (FromTextShow2 * * f a b) Source # 
type Rep1 k1 (FromTextShow2 k2 k1 f a) Source # 
type Rep1 k1 (FromTextShow2 k2 k1 f a) = D1 k1 (MetaData "FromTextShow2" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 k1 (MetaCons "FromTextShow2" PrefixI True) (S1 k1 (MetaSel (Just Symbol "fromTextShow2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 k1 (f a))))
type Rep (FromTextShow2 k1 k2 f a b) Source # 
type Rep (FromTextShow2 k1 k2 f a b) = D1 * (MetaData "FromTextShow2" "TextShow.FromStringTextShow" "text-show-3.7.2-Ac33oNMWzsX7GhPgTydUps" True) (C1 * (MetaCons "FromTextShow2" PrefixI True) (S1 * (MetaSel (Just Symbol "fromTextShow2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (f a b))))

showsPrecToShowbPrec :: (Int -> a -> ShowS) -> Int -> a -> Builder Source #

Convert a precedence-aware ShowS-based show function to a Builder-based one.

Since: 3

showsToShowb :: (a -> ShowS) -> a -> Builder Source #

Convert a ShowS-based show function to a Builder-based one.

Since: 3

showbPrecToShowsPrec :: (Int -> a -> Builder) -> Int -> a -> ShowS Source #

Convert a precedence-aware Builder-based show function to a ShowS-based one.

Since: 3

showbToShows :: (a -> Builder) -> a -> ShowS Source #

Convert a Builder-based show function to a ShowS-based one.

Since: 3

Conversions between Builder, strict Text, and lazy Text

showtPrecToShowbPrec :: (Int -> a -> Text) -> Int -> a -> Builder Source #

Convert a precedence-aware, strict Text-based show function to a Builder-based one.

Since: 3.4

showtlPrecToShowbPrec :: (Int -> a -> Text) -> Int -> a -> Builder Source #

Convert a precedence-aware, lazy Text-based show function to a Builder-based one.

Since: 3.4

showtToShowb :: (a -> Text) -> a -> Builder Source #

Convert a strict Text-based show function to a Builder-based one.

Since: 3.4

showtlToShowb :: (a -> Text) -> a -> Builder Source #

Convert a lazy Text-based show function to a Builder-based one.

Since: 3.4

showbPrecToShowtPrec :: (Int -> a -> Builder) -> Int -> a -> Text Source #

Convert a precedence-aware Builder-based show function to a strict Text-based one.

Since: 3.4

showbPrecToShowtlPrec :: (Int -> a -> Builder) -> Int -> a -> Text Source #

Convert a precedence-aware Builder-based show function to a lazy Text-based one.

Since: 3.4

showbToShowt :: (a -> Builder) -> a -> Text Source #

Convert a Builder-based show function to a strict Text-based one.

Since: 3

showbToShowtl :: (a -> Builder) -> a -> Text Source #

Convert a Builder-based show function to a lazy Text-based one.

Since: 3