{-# LANGUAGE CPP #-} module HIndent.Ast.Module.Export.Entry ( ExportEntry , mkExportEntry ) where import GHC.Stack import qualified GHC.Types.SrcLoc as GHC import qualified GHC.Unit as GHC import HIndent.Ast.NodeComments import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC import HIndent.Pretty import HIndent.Pretty.Combinators import HIndent.Pretty.NodeComments #if MIN_VERSION_ghc_lib_parser(9, 6, 1) data ExportEntry = SingleIdentifier (GHC.LIEWrappedName GHC.GhcPs) | WithSpecificConstructors (GHC.LIEWrappedName GHC.GhcPs) [GHC.LIEWrappedName GHC.GhcPs] | WithAllConstructors (GHC.LIEWrappedName GHC.GhcPs) | ByModule (GHC.GenLocated GHC.SrcSpanAnnA GHC.ModuleName) #else data ExportEntry = SingleIdentifier (GHC.LIEWrappedName (GHC.IdP GHC.GhcPs)) | WithSpecificConstructors (GHC.LIEWrappedName (GHC.IdP GHC.GhcPs)) [GHC.LIEWrappedName (GHC.IdP GHC.GhcPs)] | WithAllConstructors (GHC.LIEWrappedName (GHC.IdP GHC.GhcPs)) | ByModule (GHC.GenLocated GHC.SrcSpanAnnA GHC.ModuleName) #endif instance CommentExtraction ExportEntry where nodeComments :: ExportEntry -> NodeComments nodeComments SingleIdentifier {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] nodeComments WithSpecificConstructors {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] nodeComments WithAllConstructors {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] nodeComments ByModule {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] instance Pretty ExportEntry where pretty' :: ExportEntry -> Printer () pretty' (SingleIdentifier LIEWrappedName GhcPs s) = GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> Printer () forall a. Pretty a => a -> Printer () pretty LIEWrappedName GhcPs GenLocated SrcSpanAnnA (IEWrappedName GhcPs) s pretty' (WithSpecificConstructors LIEWrappedName GhcPs s [LIEWrappedName GhcPs] xs) = GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> Printer () forall a. Pretty a => a -> Printer () pretty LIEWrappedName GhcPs GenLocated SrcSpanAnnA (IEWrappedName GhcPs) s Printer () -> Printer () -> Printer () forall a b. Printer a -> Printer b -> Printer b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> [Printer ()] -> Printer () hTuple ((GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> Printer ()) -> [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)] -> [Printer ()] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> Printer () forall a. Pretty a => a -> Printer () pretty [LIEWrappedName GhcPs] [GenLocated SrcSpanAnnA (IEWrappedName GhcPs)] xs) pretty' (WithAllConstructors LIEWrappedName GhcPs s) = GenLocated SrcSpanAnnA (IEWrappedName GhcPs) -> Printer () forall a. Pretty a => a -> Printer () pretty LIEWrappedName GhcPs GenLocated SrcSpanAnnA (IEWrappedName GhcPs) s Printer () -> Printer () -> Printer () forall a b. Printer a -> Printer b -> Printer b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> HasCallStack => String -> Printer () String -> Printer () string String "(..)" pretty' (ByModule GenLocated SrcSpanAnnA ModuleName s) = HasCallStack => String -> Printer () String -> Printer () string String "module " Printer () -> Printer () -> Printer () forall a b. Printer a -> Printer b -> Printer b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> GenLocated SrcSpanAnnA ModuleName -> Printer () forall a. Pretty a => a -> Printer () pretty GenLocated SrcSpanAnnA ModuleName s mkExportEntry :: GHC.IE GHC.GhcPs -> ExportEntry #if MIN_VERSION_ghc_lib_parser(9, 10, 1) mkExportEntry :: IE GhcPs -> ExportEntry mkExportEntry (GHC.IEVar XIEVar GhcPs _ LIEWrappedName GhcPs name Maybe (ExportDoc GhcPs) _) = LIEWrappedName GhcPs -> ExportEntry SingleIdentifier LIEWrappedName GhcPs name mkExportEntry (GHC.IEThingAbs XIEThingAbs GhcPs _ LIEWrappedName GhcPs name Maybe (ExportDoc GhcPs) _) = LIEWrappedName GhcPs -> ExportEntry SingleIdentifier LIEWrappedName GhcPs name mkExportEntry (GHC.IEThingAll XIEThingAll GhcPs _ LIEWrappedName GhcPs name Maybe (ExportDoc GhcPs) _) = LIEWrappedName GhcPs -> ExportEntry WithAllConstructors LIEWrappedName GhcPs name mkExportEntry (GHC.IEThingWith XIEThingWith GhcPs _ LIEWrappedName GhcPs name IEWildcard _ [LIEWrappedName GhcPs] constructors Maybe (ExportDoc GhcPs) _) = LIEWrappedName GhcPs -> [LIEWrappedName GhcPs] -> ExportEntry WithSpecificConstructors LIEWrappedName GhcPs name [LIEWrappedName GhcPs] constructors #else mkExportEntry (GHC.IEVar _ name) = SingleIdentifier name mkExportEntry (GHC.IEThingAbs _ name) = SingleIdentifier name mkExportEntry (GHC.IEThingAll _ name) = WithAllConstructors name mkExportEntry (GHC.IEThingWith _ name _ constructors) = WithSpecificConstructors name constructors #endif mkExportEntry (GHC.IEModuleContents XIEModuleContents GhcPs _ XRec GhcPs ModuleName name) = GenLocated SrcSpanAnnA ModuleName -> ExportEntry ByModule XRec GhcPs ModuleName GenLocated SrcSpanAnnA ModuleName name mkExportEntry GHC.IEGroup {} = ExportEntry forall a. HasCallStack => a neverAppears mkExportEntry GHC.IEDoc {} = ExportEntry forall a. HasCallStack => a neverAppears mkExportEntry GHC.IEDocNamed {} = ExportEntry forall a. HasCallStack => a neverAppears neverAppears :: HasCallStack => a neverAppears :: forall a. HasCallStack => a neverAppears = String -> a forall a. HasCallStack => String -> a error String "This AST node should never appear in the GHC AST. If you see this error message, please report a bug to the HIndent maintainers."