#if MIN_VERSION_base(4,8,0)
#endif
module TextShow.Data.Monoid (
showbAllPrec
, showbAnyPrec
, liftShowbDualPrec
, liftShowbFirstPrec
, liftShowbLastPrec
, liftShowbProductPrec
, liftShowbSumPrec
#if MIN_VERSION_base(4,8,0)
, showbAltPrec
, liftShowbAltPrec
#endif
) where
import Data.Monoid.Compat (All, Any, Dual, First, Last, Product, Sum)
import Data.Text.Lazy.Builder (Builder)
import TextShow.Classes (TextShow(..), TextShow1(..))
import TextShow.Data.Bool ()
import TextShow.Data.Maybe ()
import TextShow.TH.Internal (deriveTextShow, deriveTextShow1)
#if MIN_VERSION_base(4,8,0)
import Data.Monoid (Alt)
import TextShow.TH.Internal (makeShowbPrec)
#endif
#include "inline.h"
showbAllPrec :: Int -> All -> Builder
showbAllPrec = showbPrec
showbAnyPrec :: Int -> Any -> Builder
showbAnyPrec = showbPrec
liftShowbDualPrec :: (Int -> a -> Builder) -> Int -> Dual a -> Builder
liftShowbDualPrec sp = liftShowbPrec sp undefined
liftShowbFirstPrec :: (Int -> a -> Builder) -> Int -> First a -> Builder
liftShowbFirstPrec sp = liftShowbPrec sp undefined
liftShowbLastPrec :: (Int -> a -> Builder) -> Int -> Last a -> Builder
liftShowbLastPrec sp = liftShowbPrec sp undefined
liftShowbProductPrec :: (Int -> a -> Builder) -> Int -> Product a -> Builder
liftShowbProductPrec sp = liftShowbPrec sp undefined
liftShowbSumPrec :: (Int -> a -> Builder) -> Int -> Sum a -> Builder
liftShowbSumPrec sp = liftShowbPrec sp undefined
#if MIN_VERSION_base(4,8,0)
showbAltPrec :: TextShow (f a) => Int -> Alt f a -> Builder
showbAltPrec = showbPrec
liftShowbAltPrec :: TextShow1 f => (Int -> a -> Builder) -> ([a] -> Builder)
-> Int -> Alt f a -> Builder
liftShowbAltPrec = liftShowbPrec
#endif
$(deriveTextShow ''All)
$(deriveTextShow ''Any)
$(deriveTextShow ''Dual)
$(deriveTextShow1 ''Dual)
$(deriveTextShow ''First)
$(deriveTextShow1 ''First)
$(deriveTextShow ''Last)
$(deriveTextShow1 ''Last)
$(deriveTextShow ''Product)
$(deriveTextShow1 ''Product)
$(deriveTextShow ''Sum)
$(deriveTextShow1 ''Sum)
#if MIN_VERSION_base(4,8,0)
instance TextShow (f a) => TextShow (Alt f a) where
showbPrec = $(makeShowbPrec ''Alt)
$(deriveTextShow1 ''Alt)
#endif