{-# LANGUAGE RecordWildCards #-} module HIndent.Ast.Declaration.Annotation.Role ( RoleAnnotation , mkRoleAnnotation ) where import HIndent.Ast.Name.Prefix import HIndent.Ast.NodeComments import HIndent.Ast.Role 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 RoleAnnotation = RoleAnnotation { RoleAnnotation -> WithComments PrefixName name :: WithComments PrefixName , RoleAnnotation -> [WithComments (Maybe Role)] roles :: [WithComments (Maybe Role)] } instance CommentExtraction RoleAnnotation where nodeComments :: RoleAnnotation -> NodeComments nodeComments RoleAnnotation {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] instance Pretty RoleAnnotation where pretty' :: RoleAnnotation -> Printer () pretty' RoleAnnotation {[WithComments (Maybe Role)] WithComments PrefixName name :: RoleAnnotation -> WithComments PrefixName roles :: RoleAnnotation -> [WithComments (Maybe Role)] name :: WithComments PrefixName roles :: [WithComments (Maybe Role)] ..} = [Printer ()] -> Printer () spaced ([Printer ()] -> Printer ()) -> [Printer ()] -> Printer () forall a b. (a -> b) -> a -> b $ [HasCallStack => String -> Printer () String -> Printer () string String "type role", WithComments PrefixName -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments PrefixName name] [Printer ()] -> [Printer ()] -> [Printer ()] forall a. [a] -> [a] -> [a] ++ (WithComments (Maybe Role) -> Printer ()) -> [WithComments (Maybe Role)] -> [Printer ()] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (WithComments (Maybe Role) -> (Maybe Role -> Printer ()) -> Printer () forall a. WithComments a -> (a -> Printer ()) -> Printer () `prettyWith` Printer () -> (Role -> Printer ()) -> Maybe Role -> Printer () forall b a. b -> (a -> b) -> Maybe a -> b maybe (HasCallStack => String -> Printer () String -> Printer () string String "_") Role -> Printer () forall a. Pretty a => a -> Printer () pretty) [WithComments (Maybe Role)] roles mkRoleAnnotation :: GHC.RoleAnnotDecl GHC.GhcPs -> RoleAnnotation mkRoleAnnotation :: RoleAnnotDecl GhcPs -> RoleAnnotation mkRoleAnnotation (GHC.RoleAnnotDecl XCRoleAnnotDecl GhcPs _ LIdP GhcPs nm [XRec GhcPs (Maybe Role)] rs) = RoleAnnotation {[WithComments (Maybe Role)] WithComments PrefixName name :: WithComments PrefixName roles :: [WithComments (Maybe Role)] name :: WithComments PrefixName roles :: [WithComments (Maybe Role)] ..} where name :: WithComments PrefixName name = 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 nm roles :: [WithComments (Maybe Role)] roles = (GenLocated EpAnnCO (Maybe Role) -> WithComments (Maybe Role)) -> [GenLocated EpAnnCO (Maybe Role)] -> [WithComments (Maybe Role)] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Maybe Role -> Maybe Role) -> WithComments (Maybe Role) -> WithComments (Maybe Role) forall a b. (a -> b) -> WithComments a -> WithComments b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Role -> Role) -> Maybe Role -> Maybe Role forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Role -> Role mkRole) (WithComments (Maybe Role) -> WithComments (Maybe Role)) -> (GenLocated EpAnnCO (Maybe Role) -> WithComments (Maybe Role)) -> GenLocated EpAnnCO (Maybe Role) -> WithComments (Maybe Role) forall b c a. (b -> c) -> (a -> b) -> a -> c . GenLocated EpAnnCO (Maybe Role) -> WithComments (Maybe Role) forall l a. CommentExtraction l => GenLocated l a -> WithComments a fromGenLocated) [XRec GhcPs (Maybe Role)] [GenLocated EpAnnCO (Maybe Role)] rs