{-# LANGUAGE CPP #-} module HIndent.Ast.Declaration.Warning.Collection ( WarningCollection , mkWarningCollection ) where import HIndent.Ast.Declaration.Warning 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 newtype WarningCollection = WarningCollection [WithComments WarningDeclaration] instance CommentExtraction WarningCollection where nodeComments :: WarningCollection -> NodeComments nodeComments WarningCollection {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] instance Pretty WarningCollection where pretty' :: WarningCollection -> Printer () pretty' (WarningCollection [WithComments WarningDeclaration] xs) = [Printer ()] -> Printer () lined ([Printer ()] -> Printer ()) -> [Printer ()] -> Printer () forall a b. (a -> b) -> a -> b $ (WithComments WarningDeclaration -> Printer ()) -> [WithComments WarningDeclaration] -> [Printer ()] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap WithComments WarningDeclaration -> Printer () forall a. Pretty a => a -> Printer () pretty [WithComments WarningDeclaration] xs mkWarningCollection :: GHC.WarnDecls GHC.GhcPs -> WarningCollection #if MIN_VERSION_ghc_lib_parser(9, 6, 1) mkWarningCollection :: WarnDecls GhcPs -> WarningCollection mkWarningCollection (GHC.Warnings XWarnings GhcPs _ [LWarnDecl GhcPs] xs) = [WithComments WarningDeclaration] -> WarningCollection WarningCollection ([WithComments WarningDeclaration] -> WarningCollection) -> [WithComments WarningDeclaration] -> WarningCollection forall a b. (a -> b) -> a -> b $ (GenLocated SrcSpanAnnA (WarnDecl GhcPs) -> WithComments WarningDeclaration) -> [GenLocated SrcSpanAnnA (WarnDecl GhcPs)] -> [WithComments WarningDeclaration] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((WarnDecl GhcPs -> WarningDeclaration) -> WithComments (WarnDecl GhcPs) -> WithComments WarningDeclaration forall a b. (a -> b) -> WithComments a -> WithComments b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap WarnDecl GhcPs -> WarningDeclaration mkWarningDeclaration (WithComments (WarnDecl GhcPs) -> WithComments WarningDeclaration) -> (GenLocated SrcSpanAnnA (WarnDecl GhcPs) -> WithComments (WarnDecl GhcPs)) -> GenLocated SrcSpanAnnA (WarnDecl GhcPs) -> WithComments WarningDeclaration forall b c a. (b -> c) -> (a -> b) -> a -> c . GenLocated SrcSpanAnnA (WarnDecl GhcPs) -> WithComments (WarnDecl GhcPs) forall l a. CommentExtraction l => GenLocated l a -> WithComments a fromGenLocated) [LWarnDecl GhcPs] [GenLocated SrcSpanAnnA (WarnDecl GhcPs)] xs #else mkWarningCollection (GHC.Warnings _ _ xs) = WarningCollection $ fmap (fmap mkWarningDeclaration . fromGenLocated) xs #endif