{-# LANGUAGE RecordWildCards #-} module HIndent.Ast.Declaration.Signature.StandaloneKind ( StandaloneKind , mkStandaloneKind ) where import qualified GHC.Hs as GHC import HIndent.Ast.Name.Prefix import HIndent.Ast.NodeComments import HIndent.Ast.WithComments import {-# SOURCE #-} HIndent.Pretty import HIndent.Pretty.Combinators import HIndent.Pretty.NodeComments data StandaloneKind = StandaloneKind { StandaloneKind -> WithComments PrefixName name :: WithComments PrefixName , StandaloneKind -> LHsSigType GhcPs kind :: GHC.LHsSigType GHC.GhcPs } instance CommentExtraction StandaloneKind where nodeComments :: StandaloneKind -> NodeComments nodeComments StandaloneKind {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] instance Pretty StandaloneKind where pretty' :: StandaloneKind -> Printer () pretty' StandaloneKind {LHsSigType GhcPs WithComments PrefixName name :: StandaloneKind -> WithComments PrefixName kind :: StandaloneKind -> LHsSigType GhcPs name :: WithComments PrefixName kind :: LHsSigType GhcPs ..} = [Printer ()] -> Printer () spaced [HasCallStack => String -> Printer () String -> Printer () string String "type", WithComments PrefixName -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments PrefixName name, HasCallStack => String -> Printer () String -> Printer () string String "::", GenLocated SrcSpanAnnA (HsSigType GhcPs) -> Printer () forall a. Pretty a => a -> Printer () pretty LHsSigType GhcPs GenLocated SrcSpanAnnA (HsSigType GhcPs) kind] mkStandaloneKind :: GHC.StandaloneKindSig GHC.GhcPs -> StandaloneKind mkStandaloneKind :: StandaloneKindSig GhcPs -> StandaloneKind mkStandaloneKind (GHC.StandaloneKindSig XStandaloneKindSig GhcPs _ LIdP GhcPs n LHsSigType GhcPs kind) = StandaloneKind {LHsSigType GhcPs WithComments PrefixName name :: WithComments PrefixName kind :: LHsSigType GhcPs kind :: LHsSigType GhcPs name :: WithComments PrefixName ..} 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 n