module HIndent.Ast.Declaration.Annotation.Provenance ( Provenance , mkProvenance ) where import HIndent.Ast.Name.Prefix import HIndent.Ast.NodeComments import HIndent.Ast.WithComments import qualified HIndent.GhcLibParserWrapper.GHC.Hs as GHC import {-# SOURCE #-} HIndent.Pretty import HIndent.Pretty.Combinators import HIndent.Pretty.NodeComments data Provenance = Value (WithComments PrefixName) | Type (WithComments PrefixName) | Module instance CommentExtraction Provenance where nodeComments :: Provenance -> NodeComments nodeComments Value {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] nodeComments Type {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] nodeComments Provenance Module = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] instance Pretty Provenance where pretty' :: Provenance -> Printer () pretty' (Value WithComments PrefixName x) = WithComments PrefixName -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments PrefixName x pretty' (Type WithComments PrefixName x) = HasCallStack => String -> Printer () String -> Printer () string String "type " Printer () -> Printer () -> Printer () forall a b. Printer a -> Printer b -> Printer b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> WithComments PrefixName -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments PrefixName x pretty' Provenance Module = HasCallStack => String -> Printer () String -> Printer () string String "module" mkProvenance :: GHC.AnnProvenance GHC.GhcPs -> Provenance mkProvenance :: AnnProvenance GhcPs -> Provenance mkProvenance (GHC.ValueAnnProvenance LIdP GhcPs x) = WithComments PrefixName -> Provenance Value (WithComments PrefixName -> Provenance) -> WithComments PrefixName -> Provenance forall a b. (a -> b) -> a -> b $ GenLocated SrcSpanAnnN PrefixName -> WithComments PrefixName forall l a. CommentExtraction l => GenLocated l a -> WithComments a fromGenLocated (GenLocated SrcSpanAnnN PrefixName -> WithComments PrefixName) -> GenLocated SrcSpanAnnN PrefixName -> WithComments PrefixName forall a b. (a -> b) -> a -> b $ (RdrName -> PrefixName) -> GenLocated SrcSpanAnnN RdrName -> GenLocated SrcSpanAnnN PrefixName forall a b. (a -> b) -> GenLocated SrcSpanAnnN a -> GenLocated SrcSpanAnnN b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap RdrName -> PrefixName mkPrefixName LIdP GhcPs GenLocated SrcSpanAnnN RdrName x mkProvenance (GHC.TypeAnnProvenance LIdP GhcPs x) = WithComments PrefixName -> Provenance Type (WithComments PrefixName -> Provenance) -> WithComments PrefixName -> Provenance forall a b. (a -> b) -> a -> b $ GenLocated SrcSpanAnnN PrefixName -> WithComments PrefixName forall l a. CommentExtraction l => GenLocated l a -> WithComments a fromGenLocated (GenLocated SrcSpanAnnN PrefixName -> WithComments PrefixName) -> GenLocated SrcSpanAnnN PrefixName -> WithComments PrefixName forall a b. (a -> b) -> a -> b $ (RdrName -> PrefixName) -> GenLocated SrcSpanAnnN RdrName -> GenLocated SrcSpanAnnN PrefixName forall a b. (a -> b) -> GenLocated SrcSpanAnnN a -> GenLocated SrcSpanAnnN b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap RdrName -> PrefixName mkPrefixName LIdP GhcPs GenLocated SrcSpanAnnN RdrName x mkProvenance AnnProvenance GhcPs GHC.ModuleAnnProvenance = Provenance Module