{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module TextShow.Data.Functor.Compose () where
import Data.Functor.Compose (Compose(..))
import TextShow.Classes (TextShow(..), TextShow1(..), showbPrec1, showbUnaryWith)
instance (TextShow1 f, TextShow1 g, TextShow a) => TextShow (Compose f g a) where
    showbPrec :: Int -> Compose f g a -> Builder
showbPrec = Int -> Compose f g a -> Builder
forall (f :: * -> *) a.
(TextShow1 f, TextShow a) =>
Int -> f a -> Builder
showbPrec1
    {-# INLINE showbPrec #-}
instance (TextShow1 f, TextShow1 g) => TextShow1 (Compose f g) where
    liftShowbPrec :: forall a.
(Int -> a -> Builder)
-> ([a] -> Builder) -> Int -> Compose f g a -> Builder
liftShowbPrec Int -> a -> Builder
sp [a] -> Builder
sl Int
p (Compose f (g a)
x) =
        (Int -> f (g a) -> Builder) -> Builder -> Int -> f (g a) -> Builder
forall a. (Int -> a -> Builder) -> Builder -> Int -> a -> Builder
showbUnaryWith ((Int -> g a -> Builder)
-> ([g a] -> Builder) -> Int -> f (g a) -> Builder
forall a.
(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) -> ([a] -> Builder) -> Int -> g a -> Builder
forall a.
(Int -> a -> Builder) -> ([a] -> Builder) -> Int -> g 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 -> a -> Builder) -> ([a] -> Builder) -> [g a] -> Builder
forall a.
(Int -> a -> Builder) -> ([a] -> Builder) -> [g a] -> Builder
forall (f :: * -> *) a.
TextShow1 f =>
(Int -> a -> Builder) -> ([a] -> Builder) -> [f a] -> Builder
liftShowbList Int -> a -> Builder
sp [a] -> Builder
sl))
                       Builder
"Compose" Int
p f (g a)
x