module StaticLS.SDoc where import qualified Data.Text as T import GHC.Plugins hiding ((<>)) showGhc :: (Outputable a) => a -> T.Text showGhc :: forall a. Outputable a => a -> Text showGhc = SDoc -> Text showSD (SDoc -> Text) -> (a -> SDoc) -> a -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . a -> SDoc forall a. Outputable a => a -> SDoc ppr showSD :: SDoc -> T.Text showSD :: SDoc -> Text showSD = String -> Text T.pack (String -> Text) -> (SDoc -> String) -> SDoc -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . SDoc -> String printSDocSimple printSDocSimple :: SDoc -> String printSDocSimple :: SDoc -> String printSDocSimple = SDocContext -> SDoc -> String renderWithContext SDocContext sdocContext where sdocContext :: SDocContext sdocContext = PprStyle -> SDocContext pprStyleToSDocContext (PprStyle -> SDocContext) -> PprStyle -> SDocContext forall a b. (a -> b) -> a -> b $ NamePprCtx -> Depth -> PprStyle mkUserStyle NamePprCtx neverQualify Depth AllTheWay pprStyleToSDocContext :: PprStyle -> SDocContext pprStyleToSDocContext :: PprStyle -> SDocContext pprStyleToSDocContext PprStyle pprStyle = SDocContext defaultSDocContext{sdocStyle = pprStyle} showNameWithoutUniques :: (Outputable a) => a -> T.Text showNameWithoutUniques :: forall a. Outputable a => a -> Text showNameWithoutUniques a outputable = String -> Text T.pack (String -> Text) -> String -> Text forall a b. (a -> b) -> a -> b $ SDocContext -> SDoc -> String renderWithContext SDocContext sdocContext (a -> SDoc forall a. Outputable a => a -> SDoc ppr a outputable) where sdocContext :: SDocContext sdocContext = PprStyle -> SDocContext pprStyleToSDocContext (PprStyle -> SDocContext) -> PprStyle -> SDocContext forall a b. (a -> b) -> a -> b $ NamePprCtx -> Depth -> PprStyle mkUserStyle NamePprCtx neverQualify Depth AllTheWay