Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 2 additions & 0 deletions src/Control/Monad/Ghc.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,9 @@ import qualified GHC.Utils.Logger as GHC
#endif
#if MIN_VERSION_ghc(9,0,0)
import qualified GHC.Utils.Monad as GHC
#if !MIN_VERSION_ghc(9,12,0)
import qualified GHC.Utils.Exception as GHC
#endif
import qualified GHC.Driver.Monad as GHC

import qualified GHC.Driver.Session as GHC
Expand Down
38 changes: 35 additions & 3 deletions src/Hint/Annotations.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,13 @@
#if MIN_VERSION_ghc(9,10,0)
{-# LANGUAGE RequiredTypeArguments #-}
#endif
module Hint.Annotations (
getModuleAnnotations,
getValAnnotations
getValAnnotations,
#if MIN_VERSION_ghc(9,10,0)
getModuleAnnotations',
getValAnnotations',
#endif
) where

import Data.Data
Expand All @@ -27,17 +34,42 @@ import MonadUtils (concatMapM)
#endif

-- Get the annotations associated with a particular module.
getModuleAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a]
getModuleAnnotations :: forall m a. (Data a, MonadInterpreter m) => a -> String -> m [a]
#if MIN_VERSION_ghc(9,10,0)
getModuleAnnotations _ = getModuleAnnotations' a
#else
getModuleAnnotations _ x = do
mods <- GHC.mgModSummaries . hsc_mod_graph <$> runGhc GHC.getSession
let x' = filter ((==) x . GHC.moduleNameString . GHC.moduleName . ms_mod) mods
concatMapM (anns . ModuleTarget . ms_mod) x'
#endif

#if MIN_VERSION_ghc(9,10,0)
-- Get the annotations associated with a particular module.
getModuleAnnotations' :: MonadInterpreter m => forall a -> Data a => String -> m [a]
getModuleAnnotations' _ x = do
mods <- GHC.mgModSummaries . hsc_mod_graph <$> runGhc GHC.getSession
let x' = filter ((==) x . GHC.moduleNameString . GHC.moduleName . ms_mod) mods
concatMapM (anns . ModuleTarget . ms_mod) x'
#endif

-- Get the annotations associated with a particular function.
getValAnnotations :: (Data a, MonadInterpreter m) => a -> String -> m [a]
getValAnnotations :: forall m a. (Data a, MonadInterpreter m) => a -> String -> m [a]
#if MIN_VERSION_ghc(9,10,0)
getValAnnotations _ = getValAnnotations' a
#else
getValAnnotations _ s = do
names <- runGhc $ GHC.parseName s
concatMapM (anns . NamedTarget) names
#endif

#if MIN_VERSION_ghc(9,10,0)
-- Get the annotations associated with a particular function.
getValAnnotations' :: MonadInterpreter m => forall a -> Data a => String -> m [a]
getValAnnotations' _ s = do
names <- runGhc $ GHC.parseName s
concatMapM (anns . NamedTarget) names
#endif

anns :: (MonadInterpreter m, Data a) => AnnTarget GHC.Name -> m [a]
anns target = runGhc $ GHC.findGlobalAnns deserializeWithData target
6 changes: 6 additions & 0 deletions src/Hint/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,9 @@ import Control.Monad.IO.Class
import Control.Monad.Catch as MC

import Data.IORef
#if !MIN_VERSION_ghc(9,12,0)
import Data.Dynamic
#endif
import qualified Data.List

import qualified Hint.GHC as GHC
Expand Down Expand Up @@ -53,7 +55,11 @@ data InterpreterError = UnknownError String
-- | GhcExceptions from the underlying GHC API are caught
-- and rethrown as this.
| GhcException String
#if MIN_VERSION_ghc(9,12,0)
deriving (Show)
#else
deriving (Show, Typeable)
#endif

data InterpreterState = St {
activePhantoms :: [PhantomModule],
Expand Down
2 changes: 2 additions & 0 deletions src/Hint/Configuration.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,9 @@ module Hint.Configuration (
import Control.Monad
import Control.Monad.Catch
import Data.Char
#if !MIN_VERSION_ghc(9,12,0)
import Data.Maybe (maybe)
#endif
import Data.List (intercalate)

import qualified Hint.GHC as GHC
Expand Down
2 changes: 2 additions & 0 deletions src/Hint/GHC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -187,7 +187,9 @@ import qualified Data.Set as Set

-- parseDynamicFlags
import qualified GHC (parseDynamicFlags)
#if !MIN_VERSION_ghc(9,12,0)
import GHC.Driver.CmdLine (Warn)
#endif

-- pprTypeForUser
import qualified GHC.Core.TyCo.Ppr as GHC (pprSigmaType)
Expand Down
7 changes: 6 additions & 1 deletion src/Hint/InterpreterT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,9 +18,11 @@ import Control.Monad.Trans.Class
import Control.Monad.Trans.Reader
import Control.Monad.Catch as MC

#if !MIN_VERSION_ghc(9,12,0)
import Data.Typeable (Typeable)
import Control.Concurrent.MVar
import System.IO.Unsafe (unsafePerformIO)
#endif

import Data.IORef
import Data.Maybe
Expand Down Expand Up @@ -152,7 +154,10 @@ ifInterpreterNotRunning action = liftIO (tryTakeMVar uniqueToken) >>= \ case
-- | The installed version of ghc is not thread-safe. This exception
-- is thrown whenever you try to execute @runInterpreter@ while another
-- instance is already running.
data MultipleInstancesNotAllowed = MultipleInstancesNotAllowed deriving Typeable
data MultipleInstancesNotAllowed = MultipleInstancesNotAllowed
#if !MIN_VERSION_ghc(9,12,0)
deriving Typeable
#endif

instance Exception MultipleInstancesNotAllowed

Expand Down
3 changes: 3 additions & 0 deletions src/Language/Haskell/Interpreter.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,9 @@ module Language.Haskell.Interpreter(
-- to mean \'{\' and \'}\' respectively. We cannot put the
-- pragmas inline in the code since GHC scarfs them up.
getModuleAnnotations, getValAnnotations,
#if MIN_VERSION_ghc(9,10,0)
getModuleAnnotations', getValAnnotations',
#endif
-- ** Type inference
typeChecksWithDetails,
typeOf, typeChecks, kindOf, normalizeType,
Expand Down