module IdeSession.Query (
Query
, ManagedFiles(..)
, InvalidSessionStateQueries(..)
, getSessionConfig
, getSourcesDir
, getDataDir
, getDistDir
, getSourceModule
, getDataFile
, getAllDataFiles
, getCabalMacros
, getCodeGeneration
, getEnv
, getArgs
, getGhcServer
, getGhcVersion
, getManagedFiles
, getBuildExeStatus
, getBuildDocStatus
, getBuildLicensesStatus
, getBreakInfo
, getSourceErrors
, getLoadedModules
, getFileMap
, getSpanInfo
, getExpTypes
, getImports
, getAutocompletion
, getPkgDeps
, getUseSites
, getDotCabal
, dumpIdInfo
, dumpAutocompletion
, dumpFileMap
) where
import Prelude hiding (mod, span)
import Control.Exception (Exception, throwIO)
import Control.Monad (forM_)
import Data.Accessor ((^.), (^:), getVal)
import Data.List (isInfixOf, sortBy)
import Data.Maybe (listToMaybe, maybeToList)
import Data.Proxy
import Data.Text (Text)
import Data.Typeable (Typeable)
import Data.Version (Version)
import System.Exit (ExitCode)
import System.FilePath ((</>))
import qualified Data.ByteString.Char8 as BSSC
import qualified Data.ByteString.Lazy as BSL
import qualified Data.Text as Text (pack, unpack)
import qualified System.FilePath.Find as Find
import IdeSession.Cabal
import IdeSession.Config
import IdeSession.GHC.API
import IdeSession.RPC.Client (ExternalException(..))
import IdeSession.State
import IdeSession.Strict.Container
import IdeSession.Types.Public
import IdeSession.Types.Translation
import IdeSession.Util.BlockingOps
import qualified IdeSession.Strict.IntMap as StrictIntMap
import qualified IdeSession.Strict.IntervalMap as StrictIntervalMap
import qualified IdeSession.Strict.List as StrictList
import qualified IdeSession.Strict.Map as StrictMap
import qualified IdeSession.Strict.Maybe as StrictMaybe
import qualified IdeSession.Strict.Trie as StrictTrie
import qualified IdeSession.Types.Private as Private
type Query a = IdeSession -> IO a
data ManagedFiles = ManagedFiles
{ sourceFiles :: [FilePath]
, dataFiles :: [FilePath]
}
deriving Show
getSessionConfig :: Query SessionConfig
getSessionConfig = staticQuery $ return . ideConfig
getSourcesDir :: Query FilePath
getSourcesDir = staticQuery $ return . ideSourceDir
getDataDir :: Query FilePath
getDataDir = staticQuery $ return . ideDataDir
getDistDir :: Query FilePath
getDistDir = staticQuery $ return . ideDistDir
getSourceModule :: FilePath -> Query BSL.ByteString
getSourceModule path = staticQuery $ BSL.readFile . (</> path) . ideSourceDir
getDataFile :: FilePath -> Query BSL.ByteString
getDataFile path = staticQuery $ BSL.readFile . (</> path) . ideDataDir
getAllDataFiles :: Query [FilePath]
getAllDataFiles = staticQuery $ \ideStaticInfo ->
Find.find Find.always
(Find.fileType Find.==? Find.RegularFile)
(ideDataDir ideStaticInfo)
getCabalMacros :: Query BSL.ByteString
getCabalMacros = staticQuery $ \IdeStaticInfo{ideDistDir} ->
BSL.readFile $ cabalMacrosLocation ideDistDir
getCodeGeneration :: Query Bool
getCodeGeneration = simpleQuery $ getVal ideGenerateCode
getEnv :: Query [(String, Maybe String)]
getEnv = simpleQuery $ getVal ideEnv
getArgs :: Query [String]
getArgs = simpleQuery $ getVal ideArgs
getGhcServer :: Query GhcServer
getGhcServer = simpleQuery $ getVal ideGhcServer
getGhcVersion :: Query GhcVersion
getGhcVersion = simpleQuery $ getVal ideGhcVersion
getManagedFiles :: Query ManagedFiles
getManagedFiles = simpleQuery $ translate . getVal ideManagedFiles
where
translate :: ManagedFilesInternal -> ManagedFiles
translate files = ManagedFiles {
sourceFiles = map fst $ _managedSource files
, dataFiles = map fst $ _managedData files
}
getBuildExeStatus :: Query (Maybe ExitCode)
getBuildExeStatus = simpleQuery $ getVal ideBuildExeStatus
getBuildDocStatus :: Query (Maybe ExitCode)
getBuildDocStatus = simpleQuery $ getVal ideBuildDocStatus
getBuildLicensesStatus :: Query (Maybe ExitCode)
getBuildLicensesStatus = simpleQuery $ getVal ideBuildLicensesStatus
getBreakInfo :: Query (Maybe BreakInfo)
getBreakInfo = simpleQuery $ toLazyMaybe . getVal ideBreakInfo
getSourceErrors :: Query [SourceError]
getSourceErrors = computedQuery $ \Computed{..} ->
toLazyList $ StrictList.map (removeExplicitSharing Proxy computedCache) computedErrors
getLoadedModules :: Query [ModuleName]
getLoadedModules = computedQuery $ \Computed{..} ->
toLazyList $ computedLoadedModules
getFileMap :: Query (FilePath -> Maybe ModuleId)
getFileMap = computedQuery $ \Computed{..} path ->
fmap (removeExplicitSharing Proxy computedCache) $
StrictMap.lookup path computedFileMap
getSpanInfo :: Query (ModuleName -> SourceSpan -> [(SourceSpan, SpanInfo)])
getSpanInfo = computedQuery $ \computed@Computed{..} mod span ->
let aux (a, b) = ( removeExplicitSharing Proxy computedCache a
, removeExplicitSharing Proxy computedCache b
)
in map aux . maybeToList $ internalGetSpanInfo computed mod span
internalGetSpanInfo :: Computed -> ModuleName -> SourceSpan
-> Maybe (Private.SourceSpan, Private.SpanInfo)
internalGetSpanInfo Computed{..} mod span = case (mSpan, mIdMap) of
(Just span', Just (Private.IdMap idMap)) ->
let doms = Private.dominators span' idMap
in listToMaybe (prioritize doms)
_ -> Nothing
where
mSpan = introduceExplicitSharing computedCache span
mIdMap = StrictMap.lookup mod computedSpanInfo
prioritize :: [(Private.SourceSpan, Private.SpanInfo)]
-> [(Private.SourceSpan, Private.SpanInfo)]
prioritize = sortBy $ \(_, a) (_, b) ->
case (a, b) of
(Private.SpanQQ _, Private.SpanId _) -> LT
(Private.SpanInSplice _, Private.SpanId _) -> LT
(Private.SpanId _, Private.SpanQQ _) -> GT
(Private.SpanId _, Private.SpanInSplice _) -> GT
(_, _) -> EQ
getExpTypes :: Query (ModuleName -> SourceSpan -> [(SourceSpan, Text)])
getExpTypes = computedQuery $ \Computed{..} mod span ->
let mSpan = introduceExplicitSharing computedCache span
mExpMap = StrictMap.lookup mod computedExpTypes
in case (mSpan, mExpMap) of
(Just span', Just (Private.ExpMap expMap)) ->
let aux (a, b) = ( removeExplicitSharing Proxy computedCache a
, b
)
doms = map aux $ Private.dominators span' expMap
in doms
_ ->
[]
getImports :: Query (ModuleName -> Maybe [Import])
getImports = computedQuery $ \Computed{..} mod ->
fmap (toLazyList . StrictList.map (removeExplicitSharing Proxy computedCache)) $
StrictMap.lookup mod computedImports
getAutocompletion :: Query (ModuleName -> String -> [IdInfo])
getAutocompletion = computedQuery $ \Computed{..} ->
autocomplete computedCache computedAutoMap
where
autocomplete :: Private.ExplicitSharingCache
-> Strict (Map ModuleName) (Strict Trie (Strict [] (XShared IdInfo)))
-> ModuleName -> String
-> [IdInfo]
autocomplete cache mapOfTries modName name =
let name' = BSSC.pack name
ns = BSSC.split '.' name'
n = if null ns then BSSC.empty else last ns
in filter (\idInfo -> name `isInfixOf` idInfoQN idInfo)
$ concatMap (toLazyList . StrictList.map (removeExplicitSharing Proxy cache))
. StrictTrie.elems
. StrictTrie.submap n
$ StrictMap.findWithDefault StrictTrie.empty modName mapOfTries
getPkgDeps :: Query (ModuleName -> Maybe [PackageId])
getPkgDeps = computedQuery $ \Computed{..} mod ->
fmap (toLazyList . StrictList.map (removeExplicitSharing Proxy computedCache)) $
StrictMap.lookup mod computedPkgDeps
getUseSites :: Query (ModuleName -> SourceSpan -> [SourceSpan])
getUseSites = computedQuery $ \computed@Computed{..} mod span ->
maybeListToList $ do
(_, spanId) <- internalGetSpanInfo computed mod span
Private.IdInfo{..} <- case spanId of
Private.SpanId idInfo -> return idInfo
Private.SpanQQ _ -> Nothing
Private.SpanInSplice idInfo -> return idInfo
return $ map (removeExplicitSharing Proxy computedCache)
. concatMap (maybeListToList . StrictMap.lookup idProp)
$ StrictMap.elems computedUseSites
where
maybeListToList :: Maybe [a] -> [a]
maybeListToList (Just xs) = xs
maybeListToList Nothing = []
getDotCabal :: Query (String -> Version -> BSL.ByteString)
getDotCabal session = withComputedState session
$ \idleState computed@Computed{..} -> do
let sourcesDir = ideSourceDir $ ideStaticInfo session
options = idleState ^. ideGhcOpts
relativeIncludes = idleState ^. ideRelativeIncludes
buildDotCabal sourcesDir relativeIncludes options computed
dumpIdInfo :: IdeSession -> IO ()
dumpIdInfo session = withComputedState session $ \_ Computed{..} ->
forM_ (StrictMap.toList computedSpanInfo) $ \(mod, idMap) -> do
putStrLn $ "*** " ++ Text.unpack mod ++ " ***"
forM_ (StrictIntervalMap.toList (Private.idMapToMap idMap)) $ \(i, idInfo) -> do
let idInfo' = removeExplicitSharing (Proxy :: Proxy SpanInfo) computedCache idInfo
(StrictIntervalMap.Interval (fn, fromLine, fromCol) (_, toLine, toCol)) = i
fn' = dereferenceFilePathPtr computedCache fn
putStrLn $ show (fn', fromLine, fromCol, toLine, toCol) ++ ": " ++ show idInfo'
dumpAutocompletion :: IdeSession -> IO ()
dumpAutocompletion session = withComputedState session $ \_ Computed{..} ->
forM_ (StrictMap.toList computedAutoMap) $ \(mod, autoMap) -> do
putStrLn $ "*** " ++ Text.unpack mod ++ " ***"
forM_ (StrictTrie.toList autoMap) $ \(key, idInfos) ->
forM_ (toLazyList idInfos) $ \idInfo -> do
let idInfo' :: IdInfo
idInfo' = removeExplicitSharing Proxy computedCache idInfo
putStrLn $ show key ++ ": " ++ show idInfo'
dumpFileMap :: IdeSession -> IO ()
dumpFileMap session = withComputedState session $ \_ Computed{..} ->
forM_ (StrictMap.toList computedFileMap) $ \(path, mod) -> do
let mod' = removeExplicitSharing (Proxy :: Proxy ModuleId) computedCache mod
putStrLn $ path ++ ": " ++ show mod'
withIdleState :: IdeSession -> (IdeIdleState -> IO a) -> IO a
withIdleState IdeSession{ideState} f =
$withStrictMVar ideState $ \st ->
case st of
IdeSessionIdle idleState -> f idleState
IdeSessionServerDied e idleState -> f (reportExAsErr e idleState)
IdeSessionShutdown -> fail "Session already shut down."
where
reportExAsErr :: ExternalException -> IdeIdleState -> IdeIdleState
reportExAsErr e = ideComputed ^:
StrictMaybe.just . updateComputed e . StrictMaybe.fromMaybe emptyComputed
updateComputed :: ExternalException -> Computed -> Computed
updateComputed (ExternalException remote _local) c =
let err = Private.SourceError {
Private.errorKind = Private.KindServerDied
, Private.errorSpan = Private.TextSpan (Text.pack "<<server died>>")
, Private.errorMsg = Text.pack remote
}
in c { computedErrors = StrictList.singleton err }
emptyComputed :: Computed
emptyComputed = Computed {
computedErrors = StrictList.nil
, computedLoadedModules = StrictList.nil
, computedFileMap = StrictMap.empty
, computedSpanInfo = StrictMap.empty
, computedExpTypes = StrictMap.empty
, computedUseSites = StrictMap.empty
, computedImports = StrictMap.empty
, computedAutoMap = StrictMap.empty
, computedPkgDeps = StrictMap.empty
, computedCache = Private.ExplicitSharingCache {
Private.filePathCache = StrictIntMap.empty
, Private.idPropCache = StrictIntMap.empty
}
}
withComputedState :: IdeSession -> (IdeIdleState -> Computed -> IO a) -> IO a
withComputedState session f = withIdleState session $ \idleState ->
case toLazyMaybe (idleState ^. ideComputed) of
Just computed -> f idleState computed
Nothing -> throwIO InvalidSessionStateQueries
data InvalidSessionStateQueries = InvalidSessionStateQueries
deriving Typeable
instance Show InvalidSessionStateQueries where
show InvalidSessionStateQueries = "This session state does not admit queries."
instance Exception InvalidSessionStateQueries
staticQuery :: (IdeStaticInfo -> IO a) -> Query a
staticQuery f = f . ideStaticInfo
simpleQuery :: (IdeIdleState -> a) -> Query a
simpleQuery f session = withIdleState session $ return . f
computedQuery :: (Computed -> a) -> Query a
computedQuery f session = withComputedState session $ const (return . f)