Copyright | (C) 2014-2017 Ryan Scott |
---|---|
License | BSD-style (see the file LICENSE) |
Maintainer | Ryan Scott |
Stability | Provisional |
Portability | GHC |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Efficiently convert from values to Text
via Builder
s.
Since: 2
Synopsis
- class TextShow a where
- showbParen :: Bool -> Builder -> Builder
- showtParen :: Bool -> Text -> Text
- showtlParen :: Bool -> Text -> Text
- showbCommaSpace :: Builder
- showtCommaSpace :: Text
- showtlCommaSpace :: Text
- showbSpace :: Builder
- showtSpace :: Text
- showtlSpace :: Text
- class (forall a. TextShow a => TextShow (f a)) => TextShow1 f where
- showbPrec1 :: (TextShow1 f, TextShow a) => Int -> f a -> Builder
- showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder
- liftShowtPrec :: TextShow1 f => (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text
- liftShowtlPrec :: TextShow1 f => (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text
- class (forall a. TextShow a => TextShow1 (f a)) => TextShow2 f where
- showbPrec2 :: (TextShow2 f, TextShow a, TextShow b) => Int -> f a b -> Builder
- showbBinaryWith :: (Int -> a -> Builder) -> (Int -> b -> Builder) -> Builder -> Int -> a -> b -> Builder
- liftShowtPrec2 :: TextShow2 f => (Int -> a -> Text) -> ([a] -> Text) -> (Int -> b -> Text) -> ([b] -> Text) -> Int -> f a b -> Text
- liftShowtlPrec2 :: TextShow2 f => (Int -> a -> Text) -> ([a] -> Text) -> (Int -> b -> Text) -> ([b] -> Text) -> Int -> f a b -> Text
- data Builder
- toText :: Builder -> Text
- toLazyText :: Builder -> Text
- toLazyTextWith :: Int -> Builder -> Text
- toString :: Builder -> String
- singleton :: Char -> Builder
- fromText :: Text -> Builder
- fromLazyText :: Text -> Builder
- fromString :: String -> Builder
- flush :: Builder
- lengthB :: Builder -> Int64
- unlinesB :: [Builder] -> Builder
- unwordsB :: [Builder] -> Builder
- printT :: TextShow a => a -> IO ()
- printTL :: TextShow a => a -> IO ()
- hPrintT :: TextShow a => Handle -> a -> IO ()
- hPrintTL :: TextShow a => Handle -> a -> IO ()
- newtype FromStringShow a = FromStringShow {
- fromStringShow :: a
- newtype FromTextShow a = FromTextShow {
- fromTextShow :: a
- newtype FromStringShow1 f a = FromStringShow1 {
- fromStringShow1 :: f a
- newtype FromTextShow1 f a = FromTextShow1 {
- fromTextShow1 :: f a
- newtype FromStringShow2 f a b = FromStringShow2 {
- fromStringShow2 :: f a b
- newtype FromTextShow2 f a b = FromTextShow2 {
- fromTextShow2 :: f a b
- showsPrecToShowbPrec :: (Int -> a -> ShowS) -> Int -> a -> Builder
- showsToShowb :: (a -> ShowS) -> a -> Builder
- showbPrecToShowsPrec :: (Int -> a -> Builder) -> Int -> a -> ShowS
- showbToShows :: (a -> Builder) -> a -> ShowS
- showtPrecToShowbPrec :: (Int -> a -> Text) -> Int -> a -> Builder
- showtlPrecToShowbPrec :: (Int -> a -> Text) -> Int -> a -> Builder
- showtToShowb :: (a -> Text) -> a -> Builder
- showtlToShowb :: (a -> Text) -> a -> Builder
- showbPrecToShowtPrec :: (Int -> a -> Builder) -> Int -> a -> Text
- showbPrecToShowtlPrec :: (Int -> a -> Builder) -> Int -> a -> Text
- showbToShowt :: (a -> Builder) -> a -> Text
- showbToShowtl :: (a -> Builder) -> a -> Text
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 Builder
s when creating TextShow
instances. As an example:
import Data.Semigroup 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 GHC.Generics.
Since: 2
:: Int | The operator precedence of the enclosing context (a number
from |
-> a | The value to be converted to a |
-> Builder |
Convert a value to a Builder
with the given predence.
Since: 2
Converts a value to a strict Text
. If you hand-define this, it should
satisfy:
showb
=showbPrec
0
Since: 2
Converts a list of values to a Builder
. By default, this is defined as
'showbList =
, but it can be overridden to allow
for specialized displaying of lists (e.g., lists of showbListWith
showb
Char
s).
Since: 2
:: Int | The operator precedence of the enclosing context (a number
from |
-> a | The value to be converted to a strict |
-> 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
Converts a value to a strict Text
. This can be overridden for
efficiency, but it should satisfy:
showt
=showtPrec
0showt
=toStrict
.showtl
The first equation is the default definition of showt
.
Since: 3
Converts a list of values to a strict Text
. This can be overridden for
efficiency, but it should satisfy:
showtList
=toStrict
.showtlList
Since: 3
:: Int | The operator precedence of the enclosing context (a number
from |
-> a | The value to be converted to a lazy |
-> 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
Converts a value to a lazy Text
. This can be overridden for
efficiency, but it should satisfy:
showtl
=showtlPrec
0showtl
=toLazyText
.showb
The first equation is the default definition of showtl
.
Since: 3
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
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 (forall a. TextShow a => TextShow (f a)) => TextShow1 f where Source #
Lifting of the TextShow
class to unary type constructors.
Since: 2
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 #
Instances
showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder Source #
produces the showbUnaryWith
sp n p xBuilder
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 (forall a. TextShow a => TextShow1 (f a)) => TextShow2 f where Source #
Lifting of the TextShow
class to binary type constructors.
Since: 2
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 #
Instances
TextShow2 Either Source # | Since: 2 |
Defined in TextShow.Data.Either | |
TextShow2 Arg Source # | Since: 3 |
Defined in TextShow.Data.Semigroup | |
TextShow2 ST Source # | Since: 2 |
Defined in TextShow.Control.Monad.ST | |
TextShow2 (,) Source # | Since: 2 |
Defined in TextShow.Data.Tuple | |
TextShow2 (Const :: Type -> Type -> Type) Source # | Since: 2 |
Defined in TextShow.Control.Applicative | |
TextShow2 (Coercion :: Type -> Type -> Type) Source # | Since: 2 |
Defined in TextShow.Data.Type.Coercion | |
TextShow2 ((:~:) :: Type -> Type -> Type) Source # | Since: 2 |
Defined in TextShow.Data.Type.Equality | |
TextShow a => TextShow2 ((,,) a) Source # | Since: 2 |
Defined in TextShow.Data.Tuple | |
TextShow2 ((:~~:) :: Type -> Type -> Type) Source # | Since: 3.6 |
Defined in TextShow.Data.Type.Equality | |
TextShow2 (K1 i :: Type -> Type -> Type) Source # | Since: 2 |
Defined in TextShow.GHC.Generics | |
(TextShow a, TextShow b) => TextShow2 ((,,,) a b) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, a0, b0)] -> Builder Source # | |
TextShow2 (->) Source # | Since: 2 |
Defined in TextShow.Functions | |
Show2 f => TextShow2 (FromStringShow2 f) Source # | Not available if using |
Defined in TextShow.FromStringTextShow 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 # | |
TextShow2 f => TextShow2 (FromTextShow2 f) Source # | |
Defined in TextShow.FromStringTextShow 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 # | |
(TextShow a, TextShow b, TextShow c) => TextShow2 ((,,,,) a b c) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d) => TextShow2 ((,,,,,) a b c d) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e) => TextShow2 ((,,,,,,) a b c d e) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f) => TextShow2 ((,,,,,,,) a b c d e f) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g) => TextShow2 ((,,,,,,,,) a b c d e f g) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h) => TextShow2 ((,,,,,,,,,) a b c d e f g h) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h, TextShow i) => TextShow2 ((,,,,,,,,,,) a b c d e f g h i) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h, TextShow i, TextShow j) => TextShow2 ((,,,,,,,,,,,) a b c d e f g h i j) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, j, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, j, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h, TextShow i, TextShow j, TextShow k) => TextShow2 ((,,,,,,,,,,,,) a b c d e f g h i j k) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, j, k, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, j, k, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h, TextShow i, TextShow j, TextShow k, TextShow l) => TextShow2 ((,,,,,,,,,,,,,) a b c d e f g h i j k l) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, j, k, l, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, j, k, l, a0, b0)] -> Builder Source # | |
(TextShow a, TextShow b, TextShow c, TextShow d, TextShow e, TextShow f, TextShow g, TextShow h, TextShow i, TextShow j, TextShow k, TextShow l, TextShow m) => TextShow2 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m) Source # | Since: 2 |
Defined in TextShow.Data.Tuple liftShowbPrec2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> Int -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a0, b0) -> Builder Source # liftShowbList2 :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> (Int -> b0 -> Builder) -> ([b0] -> Builder) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, a0, b0)] -> 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 #
produces the showbBinaryWith
sp n p x yBuilder
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
Builder
s
The Builder
type
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
.
Instances
IsString Builder | Performs replacement on invalid scalar values:
|
Defined in Data.Text.Internal.Builder fromString :: String -> Builder # | |
Monoid Builder | |
Semigroup Builder | |
Show Builder | |
Eq Builder | |
Ord Builder | |
TextShow Builder Source # | Since: 2 |
Defined in TextShow.Data.Text showbPrec :: Int -> Builder -> Builder Source # showb :: Builder -> Builder Source # showbList :: [Builder] -> Builder Source # showtPrec :: Int -> Builder -> Text Source # showt :: Builder -> Text Source # showtList :: [Builder] -> Text Source # showtlPrec :: Int -> Builder -> Text Source # showtl :: Builder -> Text Source # showtlList :: [Builder] -> Text Source # |
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.
Constructing Builder
s
singleton :: Char -> Builder #
O(1). A Builder
taking a single character, satisfying
toLazyText
(singleton
c) =singleton
c
O(1). A Builder
taking a Text
, satisfying
toLazyText
(fromText
t) =fromChunks
[t]
fromLazyText :: Text -> Builder #
O(1). A Builder
taking a lazy Text
, satisfying
toLazyText
(fromLazyText
t) = t
fromString :: String -> Builder #
O(1). A Builder taking a String
, satisfying
toLazyText
(fromString
s) =fromChunks
[S.pack s]
Performs replacement on invalid scalar values:
>>>
fromString "\55555"
"\65533"
Since: text-1.2.0.0
Flushing the buffer state
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
unlinesB :: [Builder] -> Builder Source #
Merges several Builder
s, separating them by newlines.
Since: 2
unwordsB :: [Builder] -> Builder Source #
Merges several Builder
s, 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 #
An adapter newtype, suitable for DerivingVia
.
The TextShow
instance for FromStringShow
is based on its String
Show
instance. That is,
showbPrec p (FromStringShow
x) =showsToShowb
showsPrec
p x
Since: 2
Instances
newtype FromTextShow a Source #
An adapter newtype, suitable for DerivingVia
.
The String
Show
instance for FromTextShow
is based on its
TextShow
instance. That is,
showsPrec p (FromTextShow
x) =showbToShows
showbPrec
p x
Since: 2
FromTextShow | |
|
Instances
newtype FromStringShow1 f a Source #
An adapter newtype, suitable for DerivingVia
.
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
FromStringShow1 | |
|
Instances
newtype FromTextShow1 f a Source #
An adapter newtype, suitable for DerivingVia
.
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
FromTextShow1 | |
|
Instances
newtype FromStringShow2 f a b Source #
An adapter newtype, suitable for DerivingVia
.
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
FromStringShow2 | |
|
Instances
Generic1 (FromStringShow2 f a :: k1 -> Type) Source # | |
Defined in TextShow.FromStringTextShow type Rep1 (FromStringShow2 f a) :: k -> Type # from1 :: forall (a0 :: k). FromStringShow2 f a a0 -> Rep1 (FromStringShow2 f a) a0 # to1 :: forall (a0 :: k). Rep1 (FromStringShow2 f a) a0 -> FromStringShow2 f a a0 # | |
Lift (f a b) => Lift (FromStringShow2 f a b :: Type) Source # | |
Defined in TextShow.FromStringTextShow lift :: Quote m => FromStringShow2 f a b -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => FromStringShow2 f a b -> Code m (FromStringShow2 f a b) # | |
Bifoldable f => Bifoldable (FromStringShow2 f) Source # | |
Defined in TextShow.FromStringTextShow 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 # | |
Defined in TextShow.FromStringTextShow 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 # | |
Bitraversable f => Bitraversable (FromStringShow2 f) Source # | |
Defined in TextShow.FromStringTextShow bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> FromStringShow2 f a b -> f0 (FromStringShow2 f c d) # | |
Show2 f => Show2 (FromStringShow2 f) Source # | Not available if using |
Defined in TextShow.FromStringTextShow | |
Show2 f => TextShow2 (FromStringShow2 f) Source # | Not available if using |
Defined in TextShow.FromStringTextShow 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 # | |
Foldable (f a) => Foldable (FromStringShow2 f a) Source # | |
Defined in TextShow.FromStringTextShow fold :: Monoid m => FromStringShow2 f a m -> m # foldMap :: Monoid m => (a0 -> m) -> FromStringShow2 f a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> FromStringShow2 f a a0 -> m # foldr :: (a0 -> b -> b) -> b -> FromStringShow2 f a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> FromStringShow2 f a a0 -> b # foldl :: (b -> a0 -> b) -> b -> FromStringShow2 f a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> FromStringShow2 f a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> FromStringShow2 f a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> FromStringShow2 f a a0 -> a0 # toList :: FromStringShow2 f a a0 -> [a0] # null :: FromStringShow2 f a a0 -> Bool # length :: FromStringShow2 f a a0 -> Int # elem :: Eq a0 => a0 -> FromStringShow2 f a a0 -> Bool # maximum :: Ord a0 => FromStringShow2 f a a0 -> a0 # minimum :: Ord a0 => FromStringShow2 f a a0 -> a0 # sum :: Num a0 => FromStringShow2 f a a0 -> a0 # product :: Num a0 => FromStringShow2 f a a0 -> a0 # | |
(Show2 f, Show a) => Show1 (FromStringShow2 f a) Source # | Not available if using |
Defined in TextShow.FromStringTextShow liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> FromStringShow2 f a a0 -> ShowS # liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [FromStringShow2 f a a0] -> ShowS # | |
Traversable (f a) => Traversable (FromStringShow2 f a) Source # | |
Defined in TextShow.FromStringTextShow traverse :: Applicative f0 => (a0 -> f0 b) -> FromStringShow2 f a a0 -> f0 (FromStringShow2 f a b) # sequenceA :: Applicative f0 => FromStringShow2 f a (f0 a0) -> f0 (FromStringShow2 f a a0) # mapM :: Monad m => (a0 -> m b) -> FromStringShow2 f a a0 -> m (FromStringShow2 f a b) # sequence :: Monad m => FromStringShow2 f a (m a0) -> m (FromStringShow2 f a a0) # | |
Functor (f a) => Functor (FromStringShow2 f a) Source # | |
Defined in TextShow.FromStringTextShow fmap :: (a0 -> b) -> FromStringShow2 f a a0 -> FromStringShow2 f a b # (<$) :: a0 -> FromStringShow2 f a b -> FromStringShow2 f a a0 # | |
(Show2 f, TextShow a) => TextShow1 (FromStringShow2 f a) Source # | Not available if using This instance is somewhat strange, as its instance context mixes a
|
Defined in TextShow.FromStringTextShow liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> FromStringShow2 f a a0 -> Builder Source # liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [FromStringShow2 f a a0] -> Builder Source # | |
(Typeable a, Typeable b, Typeable f, Typeable k1, Typeable k2, Data (f a b)) => Data (FromStringShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> FromStringShow2 f a b -> c (FromStringShow2 f a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromStringShow2 f a b) # toConstr :: FromStringShow2 f a b -> Constr # dataTypeOf :: FromStringShow2 f a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromStringShow2 f a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromStringShow2 f a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> FromStringShow2 f a b -> FromStringShow2 f a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow2 f a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromStringShow2 f a b -> r # gmapQ :: (forall d. Data d => d -> u) -> FromStringShow2 f a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FromStringShow2 f a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromStringShow2 f a b -> m (FromStringShow2 f a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow2 f a b -> m (FromStringShow2 f a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromStringShow2 f a b -> m (FromStringShow2 f a b) # | |
Generic (FromStringShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow type Rep (FromStringShow2 f a b) :: Type -> Type # from :: FromStringShow2 f a b -> Rep (FromStringShow2 f a b) x # to :: Rep (FromStringShow2 f a b) x -> FromStringShow2 f a b # | |
Read (f a b) => Read (FromStringShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow readsPrec :: Int -> ReadS (FromStringShow2 f a b) # readList :: ReadS [FromStringShow2 f a b] # readPrec :: ReadPrec (FromStringShow2 f a b) # readListPrec :: ReadPrec [FromStringShow2 f a b] # | |
(Show2 f, Show a, Show b) => Show (FromStringShow2 f a b) Source # | Not available if using |
Defined in TextShow.FromStringTextShow showsPrec :: Int -> FromStringShow2 f a b -> ShowS # show :: FromStringShow2 f a b -> String # showList :: [FromStringShow2 f a b] -> ShowS # | |
Eq (f a b) => Eq (FromStringShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow (==) :: FromStringShow2 f a b -> FromStringShow2 f a b -> Bool # (/=) :: FromStringShow2 f a b -> FromStringShow2 f a b -> Bool # | |
Ord (f a b) => Ord (FromStringShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow compare :: FromStringShow2 f a b -> FromStringShow2 f a b -> Ordering # (<) :: FromStringShow2 f a b -> FromStringShow2 f a b -> Bool # (<=) :: FromStringShow2 f a b -> FromStringShow2 f a b -> Bool # (>) :: FromStringShow2 f a b -> FromStringShow2 f a b -> Bool # (>=) :: FromStringShow2 f a b -> FromStringShow2 f a b -> Bool # max :: FromStringShow2 f a b -> FromStringShow2 f a b -> FromStringShow2 f a b # min :: FromStringShow2 f a b -> FromStringShow2 f a b -> FromStringShow2 f a b # | |
(Show2 f, TextShow a, TextShow b) => TextShow (FromStringShow2 f a b) Source # | Not available if using This instance is somewhat strange, as its instance context mixes a
|
Defined in TextShow.FromStringTextShow showbPrec :: Int -> FromStringShow2 f a b -> Builder Source # showb :: FromStringShow2 f a b -> Builder Source # showbList :: [FromStringShow2 f a b] -> Builder Source # showtPrec :: Int -> FromStringShow2 f a b -> Text Source # showt :: FromStringShow2 f a b -> Text Source # showtList :: [FromStringShow2 f a b] -> Text Source # showtlPrec :: Int -> FromStringShow2 f a b -> Text Source # showtl :: FromStringShow2 f a b -> Text Source # showtlList :: [FromStringShow2 f a b] -> Text Source # | |
type Rep1 (FromStringShow2 f a :: k1 -> Type) Source # | |
Defined in TextShow.FromStringTextShow type Rep1 (FromStringShow2 f a :: k1 -> Type) = D1 ('MetaData "FromStringShow2" "TextShow.FromStringTextShow" "text-show-3.10.5-9kIsI5kUu5RFXpCwih7TWK" 'True) (C1 ('MetaCons "FromStringShow2" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromStringShow2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (f a)))) | |
type Rep (FromStringShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow type Rep (FromStringShow2 f a b) = D1 ('MetaData "FromStringShow2" "TextShow.FromStringTextShow" "text-show-3.10.5-9kIsI5kUu5RFXpCwih7TWK" 'True) (C1 ('MetaCons "FromStringShow2" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromStringShow2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a b)))) |
newtype FromTextShow2 f a b Source #
An adapter newtype, suitable for DerivingVia
.
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
FromTextShow2 | |
|
Instances
Generic1 (FromTextShow2 f a :: k1 -> Type) Source # | |
Defined in TextShow.FromStringTextShow type Rep1 (FromTextShow2 f a) :: k -> Type # from1 :: forall (a0 :: k). FromTextShow2 f a a0 -> Rep1 (FromTextShow2 f a) a0 # to1 :: forall (a0 :: k). Rep1 (FromTextShow2 f a) a0 -> FromTextShow2 f a a0 # | |
Lift (f a b) => Lift (FromTextShow2 f a b :: Type) Source # | |
Defined in TextShow.FromStringTextShow lift :: Quote m => FromTextShow2 f a b -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => FromTextShow2 f a b -> Code m (FromTextShow2 f a b) # | |
Bifoldable f => Bifoldable (FromTextShow2 f) Source # | |
Defined in TextShow.FromStringTextShow 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 # | |
Defined in TextShow.FromStringTextShow 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 # | |
Bitraversable f => Bitraversable (FromTextShow2 f) Source # | |
Defined in TextShow.FromStringTextShow bitraverse :: Applicative f0 => (a -> f0 c) -> (b -> f0 d) -> FromTextShow2 f a b -> f0 (FromTextShow2 f c d) # | |
TextShow2 f => Show2 (FromTextShow2 f) Source # | Not available if using |
Defined in TextShow.FromStringTextShow | |
TextShow2 f => TextShow2 (FromTextShow2 f) Source # | |
Defined in TextShow.FromStringTextShow 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 # | |
Foldable (f a) => Foldable (FromTextShow2 f a) Source # | |
Defined in TextShow.FromStringTextShow fold :: Monoid m => FromTextShow2 f a m -> m # foldMap :: Monoid m => (a0 -> m) -> FromTextShow2 f a a0 -> m # foldMap' :: Monoid m => (a0 -> m) -> FromTextShow2 f a a0 -> m # foldr :: (a0 -> b -> b) -> b -> FromTextShow2 f a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> FromTextShow2 f a a0 -> b # foldl :: (b -> a0 -> b) -> b -> FromTextShow2 f a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> FromTextShow2 f a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> FromTextShow2 f a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> FromTextShow2 f a a0 -> a0 # toList :: FromTextShow2 f a a0 -> [a0] # null :: FromTextShow2 f a a0 -> Bool # length :: FromTextShow2 f a a0 -> Int # elem :: Eq a0 => a0 -> FromTextShow2 f a a0 -> Bool # maximum :: Ord a0 => FromTextShow2 f a a0 -> a0 # minimum :: Ord a0 => FromTextShow2 f a a0 -> a0 # sum :: Num a0 => FromTextShow2 f a a0 -> a0 # product :: Num a0 => FromTextShow2 f a a0 -> a0 # | |
(TextShow2 f, Show a) => Show1 (FromTextShow2 f a) Source # | Not available if using This instance is somewhat strange, as its instance context mixes a
This is all to say: this instance is almost surely not what you want if you
are looking to derive a |
Defined in TextShow.FromStringTextShow liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> FromTextShow2 f a a0 -> ShowS # liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [FromTextShow2 f a a0] -> ShowS # | |
Traversable (f a) => Traversable (FromTextShow2 f a) Source # | |
Defined in TextShow.FromStringTextShow traverse :: Applicative f0 => (a0 -> f0 b) -> FromTextShow2 f a a0 -> f0 (FromTextShow2 f a b) # sequenceA :: Applicative f0 => FromTextShow2 f a (f0 a0) -> f0 (FromTextShow2 f a a0) # mapM :: Monad m => (a0 -> m b) -> FromTextShow2 f a a0 -> m (FromTextShow2 f a b) # sequence :: Monad m => FromTextShow2 f a (m a0) -> m (FromTextShow2 f a a0) # | |
Functor (f a) => Functor (FromTextShow2 f a) Source # | |
Defined in TextShow.FromStringTextShow fmap :: (a0 -> b) -> FromTextShow2 f a a0 -> FromTextShow2 f a b # (<$) :: a0 -> FromTextShow2 f a b -> FromTextShow2 f a a0 # | |
(TextShow2 f, TextShow a) => TextShow1 (FromTextShow2 f a) Source # | |
Defined in TextShow.FromStringTextShow liftShowbPrec :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> Int -> FromTextShow2 f a a0 -> Builder Source # liftShowbList :: (Int -> a0 -> Builder) -> ([a0] -> Builder) -> [FromTextShow2 f a a0] -> Builder Source # | |
(Typeable a, Typeable b, Typeable f, Typeable k1, Typeable k2, Data (f a b)) => Data (FromTextShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow gfoldl :: (forall d b0. Data d => c (d -> b0) -> d -> c b0) -> (forall g. g -> c g) -> FromTextShow2 f a b -> c (FromTextShow2 f a b) # gunfold :: (forall b0 r. Data b0 => c (b0 -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FromTextShow2 f a b) # toConstr :: FromTextShow2 f a b -> Constr # dataTypeOf :: FromTextShow2 f a b -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (FromTextShow2 f a b)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FromTextShow2 f a b)) # gmapT :: (forall b0. Data b0 => b0 -> b0) -> FromTextShow2 f a b -> FromTextShow2 f a b # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow2 f a b -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FromTextShow2 f a b -> r # gmapQ :: (forall d. Data d => d -> u) -> FromTextShow2 f a b -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> FromTextShow2 f a b -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> FromTextShow2 f a b -> m (FromTextShow2 f a b) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow2 f a b -> m (FromTextShow2 f a b) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FromTextShow2 f a b -> m (FromTextShow2 f a b) # | |
Generic (FromTextShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow type Rep (FromTextShow2 f a b) :: Type -> Type # from :: FromTextShow2 f a b -> Rep (FromTextShow2 f a b) x # to :: Rep (FromTextShow2 f a b) x -> FromTextShow2 f a b # | |
Read (f a b) => Read (FromTextShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow readsPrec :: Int -> ReadS (FromTextShow2 f a b) # readList :: ReadS [FromTextShow2 f a b] # readPrec :: ReadPrec (FromTextShow2 f a b) # readListPrec :: ReadPrec [FromTextShow2 f a b] # | |
(TextShow2 f, Show a, Show b) => Show (FromTextShow2 f a b) Source # | Not available if using This instance is somewhat strange, as its instance context mixes a
This is all to say: this instance is almost surely not what you want if you
are looking to derive a |
Defined in TextShow.FromStringTextShow showsPrec :: Int -> FromTextShow2 f a b -> ShowS # show :: FromTextShow2 f a b -> String # showList :: [FromTextShow2 f a b] -> ShowS # | |
Eq (f a b) => Eq (FromTextShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow (==) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool # (/=) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool # | |
Ord (f a b) => Ord (FromTextShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow compare :: FromTextShow2 f a b -> FromTextShow2 f a b -> Ordering # (<) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool # (<=) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool # (>) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool # (>=) :: FromTextShow2 f a b -> FromTextShow2 f a b -> Bool # max :: FromTextShow2 f a b -> FromTextShow2 f a b -> FromTextShow2 f a b # min :: FromTextShow2 f a b -> FromTextShow2 f a b -> FromTextShow2 f a b # | |
(TextShow2 f, TextShow a, TextShow b) => TextShow (FromTextShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow showbPrec :: Int -> FromTextShow2 f a b -> Builder Source # showb :: FromTextShow2 f a b -> Builder Source # showbList :: [FromTextShow2 f a b] -> Builder Source # showtPrec :: Int -> FromTextShow2 f a b -> Text Source # showt :: FromTextShow2 f a b -> Text Source # showtList :: [FromTextShow2 f a b] -> Text Source # showtlPrec :: Int -> FromTextShow2 f a b -> Text Source # showtl :: FromTextShow2 f a b -> Text Source # showtlList :: [FromTextShow2 f a b] -> Text Source # | |
type Rep1 (FromTextShow2 f a :: k1 -> Type) Source # | |
Defined in TextShow.FromStringTextShow type Rep1 (FromTextShow2 f a :: k1 -> Type) = D1 ('MetaData "FromTextShow2" "TextShow.FromStringTextShow" "text-show-3.10.5-9kIsI5kUu5RFXpCwih7TWK" 'True) (C1 ('MetaCons "FromTextShow2" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromTextShow2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 (f a)))) | |
type Rep (FromTextShow2 f a b) Source # | |
Defined in TextShow.FromStringTextShow type Rep (FromTextShow2 f a b) = D1 ('MetaData "FromTextShow2" "TextShow.FromStringTextShow" "text-show-3.10.5-9kIsI5kUu5RFXpCwih7TWK" 'True) (C1 ('MetaCons "FromTextShow2" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromTextShow2") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a b)))) |
showsToShowb :: (a -> ShowS) -> a -> Builder Source #
showbToShows :: (a -> Builder) -> a -> ShowS Source #
Conversions between Builder
, strict Text
, and lazy Text
showtToShowb :: (a -> Text) -> a -> Builder Source #
showtlToShowb :: (a -> Text) -> a -> Builder Source #
showbToShowt :: (a -> Builder) -> a -> Text Source #