{-# LANGUAGE CPP #-} module HIndent.Ast.Context ( Context , mkContext ) where import HIndent.Ast.NodeComments import HIndent.Ast.Type 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 Context = Context [WithComments Type] instance CommentExtraction Context where nodeComments :: Context -> NodeComments nodeComments (Context [WithComments Type] _) = [LEpaComment] -> [LEpaComment] -> [LEpaComment] -> NodeComments NodeComments [] [] [] instance Pretty Context where pretty' :: Context -> Printer () pretty' (Context [WithComments Type] xs) = Printer () hor Printer () -> Printer () -> Printer () forall a. Printer a -> Printer a -> Printer a <-|> Printer () ver where hor :: Printer () hor = Printer () -> Printer () forall {a}. Printer a -> Printer a parensConditional (Printer () -> Printer ()) -> Printer () -> Printer () forall a b. (a -> b) -> a -> b $ [Printer ()] -> Printer () hCommaSep ([Printer ()] -> Printer ()) -> [Printer ()] -> Printer () forall a b. (a -> b) -> a -> b $ (WithComments Type -> Printer ()) -> [WithComments Type] -> [Printer ()] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap WithComments Type -> Printer () forall a. Pretty a => a -> Printer () pretty [WithComments Type] xs where parensConditional :: Printer a -> Printer a parensConditional = case [WithComments Type] xs of [WithComments Type _] -> Printer a -> Printer a forall a. a -> a id [WithComments Type] _ -> Printer a -> Printer a forall {a}. Printer a -> Printer a parens ver :: Printer () ver = case [WithComments Type] xs of [] -> HasCallStack => String -> Printer () String -> Printer () string String "()" [WithComments Type x] -> WithComments Type -> Printer () forall a. Pretty a => a -> Printer () pretty WithComments Type x [WithComments Type] _ -> [Printer ()] -> Printer () vTuple ([Printer ()] -> Printer ()) -> [Printer ()] -> Printer () forall a b. (a -> b) -> a -> b $ (WithComments Type -> Printer ()) -> [WithComments Type] -> [Printer ()] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap WithComments Type -> Printer () forall a. Pretty a => a -> Printer () pretty [WithComments Type] xs mkContext :: GHC.HsContext GHC.GhcPs -> Context mkContext :: HsContext GhcPs -> Context mkContext = [WithComments Type] -> Context Context ([WithComments Type] -> Context) -> ([GenLocated SrcSpanAnnA (HsType GhcPs)] -> [WithComments Type]) -> [GenLocated SrcSpanAnnA (HsType GhcPs)] -> Context forall b c a. (b -> c) -> (a -> b) -> a -> c . (GenLocated SrcSpanAnnA (HsType GhcPs) -> WithComments Type) -> [GenLocated SrcSpanAnnA (HsType GhcPs)] -> [WithComments Type] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((HsType GhcPs -> Type) -> WithComments (HsType GhcPs) -> WithComments Type forall a b. (a -> b) -> WithComments a -> WithComments b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap HsType GhcPs -> Type mkType (WithComments (HsType GhcPs) -> WithComments Type) -> (GenLocated SrcSpanAnnA (HsType GhcPs) -> WithComments (HsType GhcPs)) -> GenLocated SrcSpanAnnA (HsType GhcPs) -> WithComments Type forall b c a. (b -> c) -> (a -> b) -> a -> c . GenLocated SrcSpanAnnA (HsType GhcPs) -> WithComments (HsType GhcPs) forall l a. CommentExtraction l => GenLocated l a -> WithComments a fromGenLocated)