{-# LANGUAGE CPP, NoImplicitPrelude, OverloadedStrings #-}
module IHaskell.Eval.Info (info) where
import IHaskellPrelude
import IHaskell.Eval.Evaluate (typeCleaner, Interpreter)
import GHC
#if MIN_VERSION_ghc(9,2,0)
import GHC.Driver.Ppr
import Control.Monad.Catch (handle)
#elif MIN_VERSION_ghc(9,0,0)
import GHC.Utils.Outputable
import Control.Monad.Catch (handle)
#else
import Outputable
import Exception
#endif
info :: String -> Interpreter String
#if MIN_VERSION_ghc(9,0,0)
info :: String -> Interpreter String
info String
name = forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
handle SomeException -> Interpreter String
handler forall a b. (a -> b) -> a -> b
$ do
#else
info name = ghandle handler $ do
#endif
DynFlags
dflags <- forall (m :: * -> *). GhcMonad m => m DynFlags
getSessionDynFlags
#if MIN_VERSION_ghc(8,2,0)
Type
result <- forall (m :: * -> *).
GhcMonad m =>
TcRnExprMode -> String -> m Type
exprType TcRnExprMode
TM_Inst String
name
#else
result <- exprType name
#endif
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> String
typeCleaner forall a b. (a -> b) -> a -> b
$ forall a. Outputable a => DynFlags -> a -> String
showPpr DynFlags
dflags Type
result
where
handler :: SomeException -> Interpreter String
handler :: SomeException -> Interpreter String
handler SomeException
_ = forall (m :: * -> *) a. Monad m => a -> m a
return String
""