{-# LANGUAGE RecordWildCards #-} module HIndent.Ast.Type.Variable ( TypeVariable , mkTypeVariable ) where import qualified GHC.Hs as GHC import HIndent.Ast.Name.Prefix import HIndent.Ast.NodeComments import HIndent.Ast.Type import HIndent.Ast.WithComments import {-# SOURCE #-} HIndent.Pretty import HIndent.Pretty.Combinators import HIndent.Pretty.NodeComments data TypeVariable = TypeVariable { TypeVariable -> WithComments PrefixName name :: WithComments PrefixName , TypeVariable -> Maybe (WithComments Type) kind :: Maybe (WithComments Type) } instance CommentExtraction TypeVariable where nodeComments :: TypeVariable -> NodeComments nodeComments TypeVariable {} = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] instance Pretty TypeVariable where pretty' :: TypeVariable -> Printer () pretty' TypeVariable {kind :: TypeVariable -> Maybe (WithComments Type) kind = Just WithComments Type kind, WithComments PrefixName name :: TypeVariable -> WithComments PrefixName name :: WithComments PrefixName ..} = Printer () -> Printer () forall a. Printer a -> Printer a parens (Printer () -> Printer ()) -> Printer () -> Printer () forall a b. (a -> b) -> a -> b $ WithComments PrefixName -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments PrefixName name 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 " :: " 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 Type -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments Type kind pretty' TypeVariable {kind :: TypeVariable -> Maybe (WithComments Type) kind = Maybe (WithComments Type) Nothing, WithComments PrefixName name :: TypeVariable -> WithComments PrefixName name :: WithComments PrefixName ..} = WithComments PrefixName -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments PrefixName name mkTypeVariable :: GHC.HsTyVarBndr a GHC.GhcPs -> TypeVariable mkTypeVariable :: forall a. HsTyVarBndr a GhcPs -> TypeVariable mkTypeVariable (GHC.UserTyVar XUserTyVar GhcPs _ a _ LIdP GhcPs n) = TypeVariable {Maybe (WithComments Type) WithComments PrefixName forall {a}. Maybe a name :: WithComments PrefixName kind :: Maybe (WithComments Type) name :: WithComments PrefixName kind :: forall {a}. Maybe a ..} 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 kind :: Maybe a kind = Maybe a forall {a}. Maybe a Nothing mkTypeVariable (GHC.KindedTyVar XKindedTyVar GhcPs _ a _ LIdP GhcPs n LHsKind GhcPs k) = TypeVariable {Maybe (WithComments Type) WithComments PrefixName name :: WithComments PrefixName kind :: Maybe (WithComments Type) name :: WithComments PrefixName kind :: Maybe (WithComments Type) ..} 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 kind :: Maybe (WithComments Type) kind = WithComments Type -> Maybe (WithComments Type) forall a. a -> Maybe a Just (WithComments Type -> Maybe (WithComments Type)) -> WithComments Type -> Maybe (WithComments Type) forall a b. (a -> b) -> a -> b $ HsType GhcPs -> Type mkType (HsType GhcPs -> Type) -> WithComments (HsType GhcPs) -> WithComments Type forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> GenLocated SrcSpanAnnA (HsType GhcPs) -> WithComments (HsType GhcPs) forall l a. CommentExtraction l => GenLocated l a -> WithComments a fromGenLocated LHsKind GhcPs GenLocated SrcSpanAnnA (HsType GhcPs) k