#if !(MIN_VERSION_template_haskell(2,10,0))
#endif
module Text.Show.Text.Language.Haskell.TH (
#if MIN_VERSION_template_haskell(2,9,0)
      showbAnnLookupPrec
    , showbAnnTargetPrec,
#endif
      showbBodyPrec
    , showbCallconv
#if MIN_VERSION_template_haskell(2,5,0) && !(MIN_VERSION_template_haskell(2,7,0))
    , showbClassInstancePrec
#endif
    , showbClausePrec
    , showbConPrec
    , showbDecPrec
    , showbExpPrec
    , showbFamFlavour
    , showbFixityPrec
    , showbFixityDirection
    , showbForeignPrec
    , showbFunDepPrec
    , showbGuardPrec
    , showbInfoPrec
#if MIN_VERSION_template_haskell(2,8,0)
    , showbInline
#else
    , showbInlineSpecPrec
#endif
    , showbKindPrec
    , showbLitPrec
    , showbLocPrec
    , showbMatchPrec
    , showbModNamePrec
#if MIN_VERSION_template_haskell(2,9,0)
    , showbModulePrec
    , showbModuleInfoPrec
#endif
    , showbName
    , showbName'
    , showbOccNamePrec
    , showbPatPrec
#if MIN_VERSION_template_haskell(2,8,0)
    , showbPhasesPrec
#endif
    , showbPkgNamePrec
    , showbPragmaPrec
    , showbPredPrec
    , showbRangePrec
#if MIN_VERSION_template_haskell(2,9,0)
    , showbRole
#endif
#if MIN_VERSION_template_haskell(2,8,0)
    , showbRuleBndrPrec
    , showbRuleMatch
#endif
    , showbSafety
    , showbStmtPrec
    , showbStrict
#if MIN_VERSION_template_haskell(2,8,0)
    , showbTyLitPrec
#endif
    , showbTypePrec
    , showbTyVarBndrPrec
#if MIN_VERSION_template_haskell(2,9,0)
    , showbTySynEqnPrec
#endif
    , showbDoc
    ) where
import           Data.Char (isAlpha)
import           Data.Maybe (fromJust)
import qualified Data.Text.Lazy as TL (Text, dropWhile, null, tail)
import           Data.Text.Lazy (uncons)
#if !(MIN_VERSION_template_haskell(2,10,0))
import           GHC.Exts (Int(I#))
#endif
import           Language.Haskell.TH.PprLib (Doc, to_HPJ_Doc)
import           Language.Haskell.TH.Syntax
import           Prelude hiding (Show)
import           Text.Show.Text (Show(showb, showbPrec), Builder,
                                 fromString, toLazyText)
import           Text.Show.Text.Data.Integral (showbIntPrec)
import           Text.Show.Text.Text.PrettyPrint (renderB)
import           Text.Show.Text.TH (deriveShow)
import           Text.Show.Text.Utils ((<>), s)
showbBodyPrec :: Int -> Body -> Builder
showbBodyPrec = showbPrec
showbCallconv :: Callconv -> Builder
showbCallconv = showb
showbClausePrec :: Int -> Clause -> Builder
showbClausePrec = showbPrec
showbConPrec :: Int -> Con -> Builder
showbConPrec = showbPrec
showbDecPrec :: Int -> Dec -> Builder
showbDecPrec = showbPrec
showbExpPrec :: Int -> Exp -> Builder
showbExpPrec = showbPrec
showbFamFlavour :: FamFlavour -> Builder
showbFamFlavour = showb
showbFixityPrec :: Int -> Fixity -> Builder
showbFixityPrec = showbPrec
showbFixityDirection :: FixityDirection -> Builder
showbFixityDirection = showb
showbForeignPrec :: Int -> Foreign -> Builder
showbForeignPrec = showbPrec
showbFunDepPrec :: Int -> FunDep -> Builder
showbFunDepPrec = showbPrec
showbGuardPrec :: Int -> Guard -> Builder
showbGuardPrec = showbPrec
showbInfoPrec :: Int -> Info -> Builder
showbInfoPrec = showbPrec
showbKindPrec :: Int -> Kind -> Builder
#if MIN_VERSION_template_haskell(2,8,0)
showbKindPrec = showbTypePrec
#else
showbKindPrec = showbPrec
#endif
showbLitPrec :: Int -> Dec -> Builder
showbLitPrec = showbPrec
showbLocPrec :: Int -> Loc -> Builder
showbLocPrec = showbPrec
showbMatchPrec :: Int -> Match -> Builder
showbMatchPrec = showbPrec
showbModNamePrec :: Int -> ModName -> Builder
showbModNamePrec = showbPrec
showbName :: Name -> Builder
showbName = showbName' Alone
showbName' :: NameIs -> Name -> Builder
showbName' ni nm = case ni of
    Alone           -> nms
    Applied
        | pnam      -> nms
        | otherwise -> s '(' <> nms <> s ')'
    Infix
        | pnam      -> s '`' <> nms <> s '`'
        | otherwise -> nms
  where
    
    
    
    
    
    
    nms :: Builder
    nms = case nm of
               Name occ NameS         -> occB occ
               Name occ (NameQ m)     -> modB m   <> s '.' <> occB occ
               Name occ (NameG _ _ m) -> modB m   <> s '.' <> occB occ
               Name occ (NameU u)     -> occB occ <> s '_' <> showbIntPrec 0 (mkInt u)
               Name occ (NameL u)     -> occB occ <> s '_' <> showbIntPrec 0 (mkInt u)
    
#if MIN_VERSION_template_haskell(2,10,0)
    mkInt = id
#else
    mkInt i# = I# i#
#endif
    
    occB :: OccName -> Builder
    occB = fromString . occString
    
    modB :: ModName -> Builder
    modB = fromString . modString
    
    pnam :: Bool
    pnam = classify $ toLazyText nms
    
    
    
    classify :: TL.Text -> Bool
    classify t
        | TL.null t  = False 
        | otherwise = case fromJust $ uncons t of
              (x, xs) -> if isAlpha x || (x `elem` "_[]()")
                            then let t' = TL.dropWhile (/= '.') xs
                                 in if TL.null t'
                                       then True
                                       else classify $ TL.tail t'
                            else False
                                     
showbOccNamePrec :: Int -> OccName -> Builder
showbOccNamePrec = showbPrec
showbPatPrec :: Int -> Pat -> Builder
showbPatPrec = showbPrec
showbPkgNamePrec :: Int -> PkgName -> Builder
showbPkgNamePrec = showbPrec
showbPragmaPrec :: Int -> Pragma -> Builder
showbPragmaPrec = showbPrec
showbPredPrec :: Int -> Pred -> Builder
#if MIN_VERSION_template_haskell(2,10,0)
showbPredPrec = showbTypePrec
#else
showbPredPrec = showbPrec
#endif
showbRangePrec :: Int -> Range -> Builder
showbRangePrec = showbPrec
showbSafety :: Safety -> Builder
showbSafety = showb
showbStmtPrec :: Int -> Stmt -> Builder
showbStmtPrec = showbPrec
showbStrict :: Strict -> Builder
showbStrict = showb
showbTypePrec :: Int -> Type -> Builder
showbTypePrec = showbPrec
showbTyVarBndrPrec :: Int -> TyVarBndr -> Builder
showbTyVarBndrPrec = showbPrec
showbDoc :: Doc -> Builder
showbDoc = renderB . to_HPJ_Doc
#if MIN_VERSION_template_haskell(2,5,0) && !(MIN_VERSION_template_haskell(2,7,0))
showbClassInstancePrec :: Int -> ClassInstance -> Builder
showbClassInstancePrec = showbPrec
#endif
#if MIN_VERSION_template_haskell(2,8,0)
showbInline :: Inline -> Builder
showbInline = showb
showbPhasesPrec :: Int -> Phases -> Builder
showbPhasesPrec = showbPrec
showbRuleMatch :: RuleMatch -> Builder
showbRuleMatch = showb
showbRuleBndrPrec :: Int -> RuleBndr -> Builder
showbRuleBndrPrec = showbPrec
showbTyLitPrec :: Int -> TyLit -> Builder
showbTyLitPrec = showbPrec
#else
showbInlineSpecPrec :: Int -> InlineSpec -> Builder
showbInlineSpecPrec = showbPrec
#endif
#if MIN_VERSION_template_haskell(2,9,0)
showbAnnLookupPrec :: Int -> AnnLookup -> Builder
showbAnnLookupPrec = showbPrec
showbAnnTargetPrec :: Int -> AnnTarget -> Builder
showbAnnTargetPrec = showbPrec
showbModulePrec :: Int -> Module -> Builder
showbModulePrec = showbPrec
showbModuleInfoPrec :: Int -> ModuleInfo -> Builder
showbModuleInfoPrec = showbPrec
showbRole :: Role -> Builder
showbRole = showb
showbTySynEqnPrec :: Int -> TySynEqn -> Builder
showbTySynEqnPrec = showbPrec
#endif
$(deriveShow ''Body)
$(deriveShow ''Callconv)
$(deriveShow ''Clause)
$(deriveShow ''Con)
$(deriveShow ''Dec)
$(deriveShow ''Exp)
$(deriveShow ''FamFlavour)
$(deriveShow ''Fixity)
$(deriveShow ''FixityDirection)
$(deriveShow ''Foreign)
$(deriveShow ''FunDep)
$(deriveShow ''Guard)
$(deriveShow ''Info)
$(deriveShow ''Lit)
$(deriveShow ''Loc)
$(deriveShow ''Match)
$(deriveShow ''ModName)
instance Show Name where
    showb = showbName
$(deriveShow ''OccName)
$(deriveShow ''Pat)
$(deriveShow ''PkgName)
$(deriveShow ''Pragma)
$(deriveShow ''Range)
$(deriveShow ''Safety)
$(deriveShow ''Stmt)
$(deriveShow ''Strict)
$(deriveShow ''Type)
$(deriveShow ''TyVarBndr)
instance Show Doc where
    showb = showbDoc
#if MIN_VERSION_template_haskell(2,5,0) && !(MIN_VERSION_template_haskell(2,7,0))
$(deriveShow ''ClassInstance)
#endif
#if MIN_VERSION_template_haskell(2,8,0)
$(deriveShow ''Inline)
$(deriveShow ''Phases)
$(deriveShow ''RuleBndr)
$(deriveShow ''RuleMatch)
$(deriveShow ''TyLit)
#else
$(deriveShow ''InlineSpec)
$(deriveShow ''Kind)
#endif
#if MIN_VERSION_template_haskell(2,9,0)
$(deriveShow ''AnnLookup)
$(deriveShow ''AnnTarget)
$(deriveShow ''Module)
$(deriveShow ''ModuleInfo)
$(deriveShow ''Role)
$(deriveShow ''TySynEqn)
#endif
#if !(MIN_VERSION_template_haskell(2,10,0))
$(deriveShow ''Pred)
#endif