{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE OverloadedStrings          #-}
{-# LANGUAGE StandaloneDeriving         #-}
{-|
Module:      TextShow.Classes
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

The 'TextShow', 'TextShow1', and 'TextShow2' typeclasses.
-}
module TextShow.Classes where

import           Data.Data (Typeable)
import qualified Data.Text         as TS (Text, singleton)
import qualified Data.Text.IO      as TS (putStrLn, hPutStrLn)
import qualified Data.Text.Lazy    as TL (Text, singleton)
import qualified Data.Text.Lazy.IO as TL (putStrLn, hPutStrLn)
import           Data.Text.Lazy (toStrict)
import           Data.Text.Lazy.Builder (Builder, fromLazyText, fromString,
                                         fromText, singleton, toLazyText)

import           GHC.Show (appPrec, appPrec1)

import           Prelude ()
import           Prelude.Compat

import           System.IO (Handle)

import           TextShow.Utils (toString, toText)

-------------------------------------------------------------------------------

-- | 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/
class TextShow a where
    -- | Convert a value to a 'Builder' with the given predence.
    --
    -- /Since: 2/
    showbPrec :: 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
    showbPrec Int
_ = a -> Builder
forall a. TextShow a => a -> Builder
showb

    -- | Converts a value to a strict 'TS.Text'. If you hand-define this, it should
    -- satisfy:
    --
    -- @
    -- 'showb' = 'showbPrec' 0
    -- @
    --
    -- /Since: 2/
    showb :: a -- ^ The value to be converted to a 'Builder'.
          -> Builder
    showb = Int -> a -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
0

    -- | 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 'Char's).
    --
    -- /Since: 2/
    showbList :: [a] -- ^ The list of values to be converted to a 'Builder'.
              -> Builder
    showbList = (a -> Builder) -> [a] -> Builder
forall a. (a -> Builder) -> [a] -> Builder
showbListWith a -> Builder
forall a. TextShow a => a -> Builder
showb

    -- | Converts a value to a strict 'TS.Text' with the given precedence. This
    -- can be overridden for efficiency, but it should satisfy:
    --
    -- @
    -- 'showtPrec' p = 'toStrict' . 'showtlPrec' p
    -- @
    --
    -- /Since: 3/
    showtPrec :: 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 'TS.Text'.
              -> TS.Text
    showtPrec Int
p = Text -> Text
toStrict (Text -> Text) -> (a -> Text) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Text
forall a. TextShow a => Int -> a -> Text
showtlPrec Int
p

    -- | Converts a value to a strict 'TS.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/
    showt :: a -- ^ The value to be converted to a strict 'TS.Text'.
          -> TS.Text
    showt = Int -> a -> Text
forall a. TextShow a => Int -> a -> Text
showtPrec Int
0

    -- | Converts a list of values to a strict 'TS.Text'. This can be overridden for
    -- efficiency, but it should satisfy:
    --
    -- @
    -- 'showtList' = 'toStrict' . 'showtlList'
    -- @
    --
    -- /Since: 3/
    showtList :: [a] -- ^ The list of values to be converted to a strict 'TS.Text'.
              -> TS.Text
    showtList = Text -> Text
toStrict (Text -> Text) -> ([a] -> Text) -> [a] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Text
forall a. TextShow a => [a] -> Text
showtlList

    -- | Converts a value to a lazy 'TL.Text' with the given precedence. This
    -- can be overridden for efficiency, but it should satisfy:
    --
    -- @
    -- 'showtlPrec' p = 'toLazyText' . 'showbPrec' p
    -- @
    --
    -- /Since: 3/
    showtlPrec :: 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 'TL.Text'.
               -> TL.Text
    showtlPrec Int
p = Builder -> Text
toLazyText (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec Int
p

    -- | Converts a value to a lazy 'TL.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/
    showtl :: a -- ^ The value to be converted to a lazy 'TL.Text'.
           -> TL.Text
    showtl = Int -> a -> Text
forall a. TextShow a => Int -> a -> Text
showtlPrec Int
0

    -- | Converts a list of values to a lazy 'TL.Text'. This can be overridden for
    -- efficiency, but it should satisfy:
    --
    -- @
    -- 'showtlList' = 'toLazyText' . 'showbList'
    -- @
    --
    -- /Since: 3/
    showtlList :: [a] -- ^ The list of values to be converted to a lazy 'TL.Text'.
               -> TL.Text
    showtlList = Builder -> Text
toLazyText (Builder -> Text) -> ([a] -> Builder) -> [a] -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> Builder
forall a. TextShow a => [a] -> Builder
showbList

    {-# MINIMAL showbPrec | showb #-}

deriving instance Typeable TextShow

-- | Surrounds 'Builder' output with parentheses if the 'Bool' parameter is 'True'.
--
-- /Since: 2/
showbParen :: Bool -> Builder -> Builder
showbParen :: Bool -> Builder -> Builder
showbParen Bool
p Builder
builder | Bool
p         = Char -> Builder
singleton Char
'(' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
builder Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Char -> Builder
singleton Char
')'
                     | Bool
otherwise = Builder
builder

-- | Construct a 'Builder' containing a comma followed by a space.
--
-- /Since: 3.6/
showbCommaSpace :: Builder
showbCommaSpace :: Builder
showbCommaSpace = Builder
", "

-- | Construct a 'Builder' containing a single space character.
--
-- /Since: 2/
showbSpace :: Builder
showbSpace :: Builder
showbSpace = Char -> Builder
singleton Char
' '

-- | Converts a list of values into a 'Builder' in which the values are surrounded
-- by square brackets and each value is separated by a comma. The function argument
-- controls how each element is shown.
--
-- @'showbListWith' 'showb'@ is the default implementation of 'showbList' save for
-- a few special cases (e.g., 'String').
--
-- /Since: 2/
showbListWith :: (a -> Builder) -> [a] -> Builder
showbListWith :: (a -> Builder) -> [a] -> Builder
showbListWith a -> Builder
_      []     = Builder
"[]"
showbListWith a -> Builder
showbx (a
x:[a]
xs) = Char -> Builder
singleton Char
'[' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
showbx a
x Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> [a] -> Builder
go [a]
xs -- "[..
  where
    go :: [a] -> Builder
go (a
y:[a]
ys) = Char -> Builder
singleton Char
',' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> a -> Builder
showbx a
y Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> [a] -> Builder
go [a]
ys               -- ..,..
    go []     = Char -> Builder
singleton Char
']'                                    -- ..]"

-- | Surrounds strict 'TS.Text' output with parentheses if the 'Bool' parameter is 'True'.
--
-- /Since: 3.4/
showtParen :: Bool -> TS.Text -> TS.Text
showtParen :: Bool -> Text -> Text
showtParen Bool
p Text
t | Bool
p         = Char -> Text
TS.singleton Char
'(' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text
TS.singleton Char
')'
               | Bool
otherwise = Text
t

-- | Construct a strict 'TS.Text' containing a comma followed by a space.
--
-- /Since: 3.6/
showtCommaSpace :: TS.Text
showtCommaSpace :: Text
showtCommaSpace = Text
", "

-- | Construct a strict 'TS.Text' containing a single space character.
--
-- /Since: 3.4/
showtSpace :: TS.Text
showtSpace :: Text
showtSpace = Char -> Text
TS.singleton Char
' '

-- | Converts a list of values into a strict 'TS.Text' in which the values are surrounded
-- by square brackets and each value is separated by a comma. The function argument
-- controls how each element is shown.
--
-- /Since: 3.4/
showtListWith :: (a -> TS.Text) -> [a] -> TS.Text
showtListWith :: (a -> Text) -> [a] -> Text
showtListWith a -> Text
_      []     = Text
"[]"
showtListWith a -> Text
showtx (a
x:[a]
xs) = Char -> Text
TS.singleton Char
'[' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
showtx a
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [a] -> Text
go [a]
xs -- "[..
  where
    go :: [a] -> Text
go (a
y:[a]
ys) = Char -> Text
TS.singleton Char
',' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
showtx a
y Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [a] -> Text
go [a]
ys               -- ..,..
    go []     = Char -> Text
TS.singleton Char
']'                                    -- ..]"

-- | Surrounds lazy 'TL.Text' output with parentheses if the 'Bool' parameter is 'True'.
--
-- /Since: 3.4/
showtlParen :: Bool -> TL.Text -> TL.Text
showtlParen :: Bool -> Text -> Text
showtlParen Bool
p Text
t | Bool
p         = Char -> Text
TL.singleton Char
'(' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
t Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Char -> Text
TL.singleton Char
')'
                | Bool
otherwise = Text
t
{-# INLINE showtlParen #-}

-- | Construct a lazy 'TL.Text' containing a comma followed by a space.
--
-- /Since: 3.6/
showtlCommaSpace :: TL.Text
showtlCommaSpace :: Text
showtlCommaSpace = Text
", "

-- | Construct a lazy 'TL.Text' containing a single space character.
--
-- /Since: 3.4/
showtlSpace :: TL.Text
showtlSpace :: Text
showtlSpace = Char -> Text
TL.singleton Char
' '

-- | Converts a list of values into a lazy 'TL.Text' in which the values are surrounded
-- by square brackets and each value is separated by a comma. The function argument
-- controls how each element is shown.
--
-- /Since: 3.4/
showtlListWith :: (a -> TL.Text) -> [a] -> TL.Text
showtlListWith :: (a -> Text) -> [a] -> Text
showtlListWith a -> Text
_       []     = Text
"[]"
showtlListWith a -> Text
showtlx (a
x:[a]
xs) = Char -> Text
TL.singleton Char
'[' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
showtlx a
x Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [a] -> Text
go [a]
xs -- "[..
  where
    go :: [a] -> Text
go (a
y:[a]
ys) = Char -> Text
TL.singleton Char
',' Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> a -> Text
showtlx a
y Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> [a] -> Text
go [a]
ys                 -- ..,..
    go []     = Char -> Text
TL.singleton Char
']'                                       -- ..]"

-- | Writes a value's strict 'TS.Text' representation to the standard output, followed
--   by a newline.
--
-- /Since: 2/
printT :: TextShow a => a -> IO ()
printT :: a -> IO ()
printT = Text -> IO ()
TS.putStrLn (Text -> IO ()) -> (a -> Text) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. TextShow a => a -> Text
showt
{-# INLINE printT #-}

-- | Writes a value's lazy 'TL.Text' representation to the standard output, followed
--   by a newline.
--
-- /Since: 2/
printTL :: TextShow a => a -> IO ()
printTL :: a -> IO ()
printTL = Text -> IO ()
TL.putStrLn (Text -> IO ()) -> (a -> Text) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. TextShow a => a -> Text
showtl
{-# INLINE printTL #-}

-- | Writes a value's strict 'TS.Text' representation to a file handle, followed
--   by a newline.
--
-- /Since: 2/
hPrintT :: TextShow a => Handle -> a -> IO ()
hPrintT :: Handle -> a -> IO ()
hPrintT Handle
h = Handle -> Text -> IO ()
TS.hPutStrLn Handle
h (Text -> IO ()) -> (a -> Text) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. TextShow a => a -> Text
showt
{-# INLINE hPrintT #-}

-- | Writes a value's lazy 'TL.Text' representation to a file handle, followed
--   by a newline.
--
-- /Since: 2/
hPrintTL :: TextShow a => Handle -> a -> IO ()
hPrintTL :: Handle -> a -> IO ()
hPrintTL Handle
h = Handle -> Text -> IO ()
TL.hPutStrLn Handle
h (Text -> IO ()) -> (a -> Text) -> a -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
forall a. TextShow a => a -> Text
showtl
{-# INLINE hPrintTL #-}

-- | Convert a precedence-aware 'ShowS'-based show function to a 'Builder'-based one.
--
-- /Since: 3/
showsPrecToShowbPrec :: (Int -> a -> ShowS) -> Int -> a -> Builder
showsPrecToShowbPrec :: (Int -> a -> ShowS) -> Int -> a -> Builder
showsPrecToShowbPrec Int -> a -> ShowS
sp Int
p a
x = String -> Builder
fromString (String -> Builder) -> String -> Builder
forall a b. (a -> b) -> a -> b
$ Int -> a -> ShowS
sp Int
p a
x String
""
{-# INLINE showsPrecToShowbPrec #-}

-- | Convert a precedence-aware, strict 'TS.Text'-based show function to a 'Builder'-based one.
--
-- /Since: 3.4/
showtPrecToShowbPrec :: (Int -> a -> TS.Text) -> Int -> a -> Builder
showtPrecToShowbPrec :: (Int -> a -> Text) -> Int -> a -> Builder
showtPrecToShowbPrec Int -> a -> Text
sp Int
p = Text -> Builder
fromText (Text -> Builder) -> (a -> Text) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Text
sp Int
p
{-# INLINE showtPrecToShowbPrec #-}

-- | Convert a precedence-aware, lazy 'TL.Text'-based show function to a 'Builder'-based one.
--
-- /Since: 3.4/
showtlPrecToShowbPrec :: (Int -> a -> TL.Text) -> Int -> a -> Builder
showtlPrecToShowbPrec :: (Int -> a -> Text) -> Int -> a -> Builder
showtlPrecToShowbPrec Int -> a -> Text
sp Int
p = Text -> Builder
fromLazyText (Text -> Builder) -> (a -> Text) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Text
sp Int
p
{-# INLINE showtlPrecToShowbPrec #-}

-- | Convert a 'ShowS'-based show function to a 'Builder'-based one.
--
-- /Since: 3/
showsToShowb :: (a -> ShowS) -> a -> Builder
showsToShowb :: (a -> ShowS) -> a -> Builder
showsToShowb a -> ShowS
sf a
x = String -> Builder
fromString (String -> Builder) -> String -> Builder
forall a b. (a -> b) -> a -> b
$ a -> ShowS
sf a
x String
""
{-# INLINE showsToShowb #-}

-- | Convert a strict 'TS.Text'-based show function to a 'Builder'-based one.
--
-- /Since: 3.4/
showtToShowb :: (a -> TS.Text) -> a -> Builder
showtToShowb :: (a -> Text) -> a -> Builder
showtToShowb a -> Text
sf = Text -> Builder
fromText (Text -> Builder) -> (a -> Text) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
sf
{-# INLINE showtToShowb #-}

-- | Convert a lazy 'TL.Text'-based show function to a 'Builder'-based one.
--
-- /Since: 3.4/
showtlToShowb :: (a -> TL.Text) -> a -> Builder
showtlToShowb :: (a -> Text) -> a -> Builder
showtlToShowb a -> Text
sf = Text -> Builder
fromLazyText (Text -> Builder) -> (a -> Text) -> a -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Text
sf
{-# INLINE showtlToShowb #-}

-- | Convert a precedence-aware 'Builder'-based show function to a 'ShowS'-based one.
--
-- /Since: 3/
showbPrecToShowsPrec :: (Int -> a -> Builder) -> Int -> a -> ShowS
showbPrecToShowsPrec :: (Int -> a -> Builder) -> Int -> a -> ShowS
showbPrecToShowsPrec Int -> a -> Builder
sp Int
p = String -> ShowS
showString (String -> ShowS) -> (a -> String) -> a -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> String
toString (Builder -> String) -> (a -> Builder) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Builder
sp Int
p
{-# INLINE showbPrecToShowsPrec #-}

-- | Convert a precedence-aware 'Builder'-based show function to a strict 'TS.Text'-based one.
--
-- /Since: 3.4/
showbPrecToShowtPrec :: (Int -> a -> Builder) -> Int -> a -> TS.Text
showbPrecToShowtPrec :: (Int -> a -> Builder) -> Int -> a -> Text
showbPrecToShowtPrec Int -> a -> Builder
sp Int
p = Builder -> Text
toText (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Builder
sp Int
p
{-# INLINE showbPrecToShowtPrec #-}

-- | Convert a precedence-aware 'Builder'-based show function to a lazy 'TL.Text'-based one.
--
-- /Since: 3.4/
showbPrecToShowtlPrec :: (Int -> a -> Builder) -> Int -> a -> TL.Text
showbPrecToShowtlPrec :: (Int -> a -> Builder) -> Int -> a -> Text
showbPrecToShowtlPrec Int -> a -> Builder
sp Int
p = Builder -> Text
toLazyText (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> a -> Builder
sp Int
p
{-# INLINE showbPrecToShowtlPrec #-}

-- | Convert a 'Builder'-based show function to a 'ShowS'-based one.
--
-- /Since: 3/
showbToShows :: (a -> Builder) -> a -> ShowS
showbToShows :: (a -> Builder) -> a -> ShowS
showbToShows a -> Builder
sf = String -> ShowS
showString (String -> ShowS) -> (a -> String) -> a -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Builder -> String
toString (Builder -> String) -> (a -> Builder) -> a -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
sf
{-# INLINE showbToShows #-}

-- | Convert a 'Builder'-based show function to a strict 'TS.Text'-based one.
--
-- /Since: 3/
showbToShowt :: (a -> Builder) -> a -> TS.Text
showbToShowt :: (a -> Builder) -> a -> Text
showbToShowt a -> Builder
sf = Builder -> Text
toText (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
sf
{-# INLINE showbToShowt #-}

-- | Convert a 'Builder'-based show function to a lazy 'TL.Text'-based one.
--
-- /Since: 3/
showbToShowtl :: (a -> Builder) -> a -> TL.Text
showbToShowtl :: (a -> Builder) -> a -> Text
showbToShowtl a -> Builder
sf = Builder -> Text
toLazyText (Builder -> Text) -> (a -> Builder) -> a -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Builder
sf
{-# INLINE showbToShowtl #-}

-------------------------------------------------------------------------------

-- | Lifting of the 'TextShow' class to unary type constructors.
--
-- /Since: 2/
class TextShow1 f where
    -- | 'showbPrec' function for an application of the type constructor
    -- based on 'showbPrec' and 'showbList' functions for the argument type.
    --
    -- /Since: 3/
    liftShowbPrec :: (Int -> a -> Builder) -> ([a] -> Builder)
                  -> Int -> f a -> Builder

    -- | '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/
    liftShowbList :: (Int -> a -> Builder) -> ([a] -> Builder)
                  -> [f a] -> Builder
    liftShowbList Int -> a -> Builder
sp [a] -> Builder
sl = (f a -> Builder) -> [f a] -> Builder
forall a. (a -> Builder) -> [a] -> Builder
showbListWith ((Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
forall (f :: * -> *) a.
TextShow1 f =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
liftShowbPrec Int -> a -> Builder
sp [a] -> Builder
sl Int
0)

    {-# MINIMAL liftShowbPrec #-}

deriving instance Typeable TextShow1

-- | Lift the standard 'showbPrec' and 'showbList' functions through the
-- type constructor.
--
-- /Since: 2/
showbPrec1 :: (TextShow1 f, TextShow a) => Int -> f a -> Builder
showbPrec1 :: Int -> f a -> Builder
showbPrec1 = (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
forall (f :: * -> *) a.
TextShow1 f =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
liftShowbPrec Int -> a -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec [a] -> Builder
forall a. TextShow a => [a] -> Builder
showbList
{-# INLINE showbPrec1 #-}

-- | @'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/
showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder
showbUnaryWith :: (Int -> a -> Builder) -> Builder -> Int -> a -> Builder
showbUnaryWith Int -> a -> Builder
sp Builder
nameB Int
p a
x = Bool -> Builder -> Builder
showbParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
appPrec) (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$
    Builder
nameB Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
showbSpace Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> a -> Builder
sp Int
appPrec1 a
x
{-# INLINE showbUnaryWith #-}

-- | '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/
liftShowtPrec :: TextShow1 f => (Int -> a -> TS.Text) -> ([a] -> TS.Text)
              -> Int -> f a -> TS.Text
liftShowtPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text
liftShowtPrec Int -> a -> Text
sp [a] -> Text
sl = (Int -> f a -> Builder) -> Int -> f a -> Text
forall a. (Int -> a -> Builder) -> Int -> a -> Text
showbPrecToShowtPrec ((Int -> f a -> Builder) -> Int -> f a -> Text)
-> (Int -> f a -> Builder) -> Int -> f a -> Text
forall a b. (a -> b) -> a -> b
$ (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
forall (f :: * -> *) a.
TextShow1 f =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
liftShowbPrec ((Int -> a -> Text) -> Int -> a -> Builder
forall a. (Int -> a -> Text) -> Int -> a -> Builder
showtPrecToShowbPrec Int -> a -> Text
sp) (([a] -> Text) -> [a] -> Builder
forall a. (a -> Text) -> a -> Builder
showtToShowb [a] -> Text
sl)

-- | '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/
liftShowtlPrec :: TextShow1 f => (Int -> a -> TL.Text) -> ([a] -> TL.Text)
               -> Int -> f a -> TL.Text
liftShowtlPrec :: (Int -> a -> Text) -> ([a] -> Text) -> Int -> f a -> Text
liftShowtlPrec Int -> a -> Text
sp [a] -> Text
sl = (Int -> f a -> Builder) -> Int -> f a -> Text
forall a. (Int -> a -> Builder) -> Int -> a -> Text
showbPrecToShowtlPrec ((Int -> f a -> Builder) -> Int -> f a -> Text)
-> (Int -> f a -> Builder) -> Int -> f a -> Text
forall a b. (a -> b) -> a -> b
$ (Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
forall (f :: * -> *) a.
TextShow1 f =>
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> f a -> Builder
liftShowbPrec ((Int -> a -> Text) -> Int -> a -> Builder
forall a. (Int -> a -> Text) -> Int -> a -> Builder
showtlPrecToShowbPrec Int -> a -> Text
sp) (([a] -> Text) -> [a] -> Builder
forall a. (a -> Text) -> a -> Builder
showtlToShowb [a] -> Text
sl)

-------------------------------------------------------------------------------

-- | Lifting of the 'TextShow' class to binary type constructors.
--
-- /Since: 2/
class TextShow2 f where
    -- | 'showbPrec' function for an application of the type constructor
    -- based on 'showbPrec' and 'showbList' functions for the argument types.
    --
    -- /Since: 3/
    liftShowbPrec2 :: (Int -> a -> Builder) -> ([a] -> Builder)
                   -> (Int -> b -> Builder) -> ([b] -> Builder)
                   -> Int -> f a b -> Builder

    -- | '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/
    liftShowbList2 :: (Int -> a -> Builder) -> ([a] -> Builder)
                   -> (Int -> b -> Builder) -> ([b] -> Builder)
                   -> [f a b] -> Builder
    liftShowbList2 Int -> a -> Builder
sp1 [a] -> Builder
sl1 Int -> b -> Builder
sp2 [b] -> Builder
sl2 =
        (f a b -> Builder) -> [f a b] -> Builder
forall a. (a -> Builder) -> [a] -> Builder
showbListWith ((Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
forall (f :: * -> * -> *) a b.
TextShow2 f =>
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
liftShowbPrec2 Int -> a -> Builder
sp1 [a] -> Builder
sl1 Int -> b -> Builder
sp2 [b] -> Builder
sl2 Int
0)

    {-# MINIMAL liftShowbPrec2 #-}

deriving instance Typeable TextShow2

-- | Lift two 'showbPrec' functions through the type constructor.
--
-- /Since: 2/
showbPrec2 :: (TextShow2 f, TextShow a, TextShow b) => Int -> f a b -> Builder
showbPrec2 :: Int -> f a b -> Builder
showbPrec2 = (Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
forall (f :: * -> * -> *) a b.
TextShow2 f =>
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
liftShowbPrec2 Int -> a -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec [a] -> Builder
forall a. TextShow a => [a] -> Builder
showbList Int -> b -> Builder
forall a. TextShow a => Int -> a -> Builder
showbPrec [b] -> Builder
forall a. TextShow a => [a] -> Builder
showbList
{-# INLINE showbPrec2 #-}

-- | @'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/
showbBinaryWith :: (Int -> a -> Builder) -> (Int -> b -> Builder) ->
    Builder -> Int -> a -> b -> Builder
showbBinaryWith :: (Int -> a -> Builder)
-> (Int -> b -> Builder) -> Builder -> Int -> a -> b -> Builder
showbBinaryWith Int -> a -> Builder
sp1 Int -> b -> Builder
sp2 Builder
nameB Int
p a
x b
y = Bool -> Builder -> Builder
showbParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
appPrec) (Builder -> Builder) -> Builder -> Builder
forall a b. (a -> b) -> a -> b
$ Builder
nameB
    Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
showbSpace Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> a -> Builder
sp1 Int
appPrec1 a
x
    Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Builder
showbSpace Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> b -> Builder
sp2 Int
appPrec1 b
y
{-# INLINE showbBinaryWith #-}

-- | '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/
liftShowtPrec2 :: TextShow2 f
               => (Int -> a -> TS.Text) -> ([a] -> TS.Text)
               -> (Int -> b -> TS.Text) -> ([b] -> TS.Text)
               -> Int -> f a b -> TS.Text
liftShowtPrec2 :: (Int -> a -> Text)
-> ([a] -> Text)
-> (Int -> b -> Text)
-> ([b] -> Text)
-> Int
-> f a b
-> Text
liftShowtPrec2 Int -> a -> Text
sp1 [a] -> Text
sl1 Int -> b -> Text
sp2 [b] -> Text
sl2 = (Int -> f a b -> Builder) -> Int -> f a b -> Text
forall a. (Int -> a -> Builder) -> Int -> a -> Text
showbPrecToShowtPrec ((Int -> f a b -> Builder) -> Int -> f a b -> Text)
-> (Int -> f a b -> Builder) -> Int -> f a b -> Text
forall a b. (a -> b) -> a -> b
$
    (Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
forall (f :: * -> * -> *) a b.
TextShow2 f =>
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
liftShowbPrec2 ((Int -> a -> Text) -> Int -> a -> Builder
forall a. (Int -> a -> Text) -> Int -> a -> Builder
showtPrecToShowbPrec Int -> a -> Text
sp1) (([a] -> Text) -> [a] -> Builder
forall a. (a -> Text) -> a -> Builder
showtToShowb [a] -> Text
sl1)
                   ((Int -> b -> Text) -> Int -> b -> Builder
forall a. (Int -> a -> Text) -> Int -> a -> Builder
showtPrecToShowbPrec Int -> b -> Text
sp2) (([b] -> Text) -> [b] -> Builder
forall a. (a -> Text) -> a -> Builder
showtToShowb [b] -> Text
sl2)

-- | '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/
liftShowtlPrec2 :: TextShow2 f
                => (Int -> a -> TL.Text) -> ([a] -> TL.Text)
                -> (Int -> b -> TL.Text) -> ([b] -> TL.Text)
                -> Int -> f a b -> TL.Text
liftShowtlPrec2 :: (Int -> a -> Text)
-> ([a] -> Text)
-> (Int -> b -> Text)
-> ([b] -> Text)
-> Int
-> f a b
-> Text
liftShowtlPrec2 Int -> a -> Text
sp1 [a] -> Text
sl1 Int -> b -> Text
sp2 [b] -> Text
sl2 = (Int -> f a b -> Builder) -> Int -> f a b -> Text
forall a. (Int -> a -> Builder) -> Int -> a -> Text
showbPrecToShowtlPrec ((Int -> f a b -> Builder) -> Int -> f a b -> Text)
-> (Int -> f a b -> Builder) -> Int -> f a b -> Text
forall a b. (a -> b) -> a -> b
$
    (Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
forall (f :: * -> * -> *) a b.
TextShow2 f =>
(Int -> a -> Builder)
-> ([a] -> Builder)
-> (Int -> b -> Builder)
-> ([b] -> Builder)
-> Int
-> f a b
-> Builder
liftShowbPrec2 ((Int -> a -> Text) -> Int -> a -> Builder
forall a. (Int -> a -> Text) -> Int -> a -> Builder
showtlPrecToShowbPrec Int -> a -> Text
sp1) (([a] -> Text) -> [a] -> Builder
forall a. (a -> Text) -> a -> Builder
showtlToShowb [a] -> Text
sl1)
                   ((Int -> b -> Text) -> Int -> b -> Builder
forall a. (Int -> a -> Text) -> Int -> a -> Builder
showtlPrecToShowbPrec Int -> b -> Text
sp2) (([b] -> Text) -> [b] -> Builder
forall a. (a -> Text) -> a -> Builder
showtlToShowb [b] -> Text
sl2)