{-# LANGUAGE NoImplicitPrelude, CPP, OverloadedStrings, DoAndIfThenElse, FlexibleContexts #-}
module IHaskell.Eval.Inspect (inspect) where
import IHaskellPrelude
import qualified Prelude as P
import Data.List.Split (splitOn)
#if MIN_VERSION_ghc(9,0,0)
import qualified Control.Monad.Catch as MC
#else
import Exception (ghandle)
#endif
import IHaskell.Eval.Evaluate (Interpreter)
import IHaskell.Display
import IHaskell.Eval.Util (getType)
operatorChars :: String
operatorChars :: String
operatorChars = String
"!#$%&*+./<=>?@\\^|-~:"
whitespace :: String
whitespace :: String
whitespace = String
" \t\n"
getIdentifier :: String -> Int -> String
getIdentifier :: String -> Int -> String
getIdentifier String
code Int
_pos = String
identifier
where
chunks :: [String]
chunks = forall a. Eq a => [a] -> [a] -> [[a]]
splitOn String
whitespace String
code
lastChunk :: String
lastChunk = forall a. [a] -> a
P.last [String]
chunks :: String
identifier :: String
identifier =
if forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` String
operatorChars) String
lastChunk
then String
"(" forall a. [a] -> [a] -> [a]
++ String
lastChunk forall a. [a] -> [a] -> [a]
++ String
")"
else String
lastChunk
inspect :: String
-> Int
-> Interpreter (Maybe Display)
inspect :: String -> Int -> Interpreter (Maybe Display)
inspect String
code Int
pos = do
let identifier :: String
identifier = String -> Int -> String
getIdentifier String
code Int
pos
handler :: SomeException -> Interpreter (Maybe a)
handler :: forall a. SomeException -> Interpreter (Maybe a)
handler SomeException
_ = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
#if MIN_VERSION_ghc(9,0,0)
Maybe String
response <- forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
(e -> m a) -> m a -> m a
MC.handle forall a. SomeException -> Interpreter (Maybe a)
handler (forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). GhcMonad m => String -> m String
getType String
identifier)
#else
response <- ghandle handler (Just <$> getType identifier)
#endif
let prefix :: String
prefix = String
identifier forall a. [a] -> [a] -> [a]
++ String
" :: "
fmt :: String -> Display
fmt String
str = [DisplayData] -> Display
Display [String -> DisplayData
plain forall a b. (a -> b) -> a -> b
$ String
prefix forall a. [a] -> [a] -> [a]
++ String
str]
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ String -> Display
fmt forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
response