#if MIN_VERSION_base(4,8,0)
#endif
module Text.Show.Text.Data.Monoid (
showbAllPrec
, showbAnyPrec
, showbDualPrecWith
, showbFirstPrecWith
, showbLastPrecWith
, showbProductPrecWith
, showbSumPrecWith
#if MIN_VERSION_base(4,8,0)
, showbAltPrec
, showbAltPrecWith
#endif
) where
import Data.Monoid.Compat (All, Any, Dual, First, Last, Product, Sum)
import Data.Text.Lazy.Builder (Builder)
import Prelude hiding (Show)
import Text.Show.Text.Classes (Show(showbPrec), showbPrecWith)
import Text.Show.Text.Data.Bool ()
import Text.Show.Text.Data.Maybe ()
import Text.Show.Text.TH.Internal (deriveShow, deriveShow1)
#if MIN_VERSION_base(4,8,0)
import Data.Monoid (Alt)
import Text.Show.Text.Classes (Show1)
import Text.Show.Text.TH.Internal (mkShowbPrec)
#endif
#include "inline.h"
showbAllPrec :: Int -> All -> Builder
showbAllPrec = showbPrec
showbAnyPrec :: Int -> Any -> Builder
showbAnyPrec = showbPrec
showbDualPrecWith :: (Int -> a -> Builder) -> Int -> Dual a -> Builder
showbDualPrecWith = showbPrecWith
showbFirstPrecWith :: (Int -> a -> Builder) -> Int -> First a -> Builder
showbFirstPrecWith = showbPrecWith
showbLastPrecWith :: (Int -> a -> Builder) -> Int -> Last a -> Builder
showbLastPrecWith = showbPrecWith
showbProductPrecWith :: (Int -> a -> Builder) -> Int -> Product a -> Builder
showbProductPrecWith = showbPrecWith
showbSumPrecWith :: (Int -> a -> Builder) -> Int -> Sum a -> Builder
showbSumPrecWith = showbPrecWith
#if MIN_VERSION_base(4,8,0)
showbAltPrec :: Show (f a) => Int -> Alt f a -> Builder
showbAltPrec = showbPrec
showbAltPrecWith :: Show1 f => (Int -> a -> Builder) -> Int -> Alt f a -> Builder
showbAltPrecWith = showbPrecWith
#endif
$(deriveShow ''All)
$(deriveShow ''Any)
$(deriveShow ''Dual)
$(deriveShow1 ''Dual)
$(deriveShow ''First)
$(deriveShow1 ''First)
$(deriveShow ''Last)
$(deriveShow1 ''Last)
$(deriveShow ''Product)
$(deriveShow1 ''Product)
$(deriveShow ''Sum)
$(deriveShow1 ''Sum)
#if MIN_VERSION_base(4,8,0)
instance Show (f a) => Show (Alt f a) where
showbPrec = $(mkShowbPrec ''Alt)
$(deriveShow1 ''Alt)
#endif