-- Copyright (c) 2019 The DAML Authors. All rights reserved.
-- SPDX-License-Identifier: Apache-2.0

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE RankNTypes        #-}
{-# LANGUAGE TypeFamilies      #-}

-- | A Shake implementation of the compiler service, built
--   using the "Shaker" abstraction layer for in-memory use.
--
module Development.IDE.Core.Service(
    getIdeOptions, getIdeOptionsIO,
    IdeState, initialise, shutdown,
    runAction,
    getDiagnostics,
    ideLogger,
    updatePositionMapping,
    Log(..),
    ) where

import           Control.Applicative             ((<|>))
import           Development.IDE.Core.Debouncer
import           Development.IDE.Core.FileExists (fileExistsRules)
import           Development.IDE.Core.OfInterest hiding (Log, LogShake)
import           Development.IDE.Graph
import           Development.IDE.Types.Logger    as Logger (Logger,
                                                            Pretty (pretty),
                                                            Priority (Debug),
                                                            Recorder,
                                                            WithPriority,
                                                            cmapWithPrio)
import           Development.IDE.Types.Options   (IdeOptions (..))
import           Ide.Plugin.Config
import qualified Language.LSP.Server             as LSP
import qualified Language.LSP.Types              as LSP

import           Control.Monad
import qualified Development.IDE.Core.FileExists as FileExists
import qualified Development.IDE.Core.OfInterest as OfInterest
import           Development.IDE.Core.Shake      hiding (Log)
import qualified Development.IDE.Core.Shake      as Shake
import           Development.IDE.Types.Shake     (WithHieDb)
import           System.Environment              (lookupEnv)


data Log
  = LogShake Shake.Log
  | LogOfInterest OfInterest.Log
  | LogFileExists FileExists.Log
  deriving Int -> Log -> ShowS
[Log] -> ShowS
Log -> String
(Int -> Log -> ShowS)
-> (Log -> String) -> ([Log] -> ShowS) -> Show Log
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Log] -> ShowS
$cshowList :: [Log] -> ShowS
show :: Log -> String
$cshow :: Log -> String
showsPrec :: Int -> Log -> ShowS
$cshowsPrec :: Int -> Log -> ShowS
Show

instance Pretty Log where
  pretty :: Log -> Doc ann
pretty = \case
    LogShake Log
log      -> Log -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Log
log
    LogOfInterest Log
log -> Log -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Log
log
    LogFileExists Log
log -> Log -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Log
log

------------------------------------------------------------
-- Exposed API

-- | Initialise the Compiler Service.
initialise :: Recorder (WithPriority Log)
           -> Config
           -> Rules ()
           -> Maybe (LSP.LanguageContextEnv Config)
           -> Logger
           -> Debouncer LSP.NormalizedUri
           -> IdeOptions
           -> WithHieDb
           -> IndexQueue
           -> IO IdeState
initialise :: Recorder (WithPriority Log)
-> Config
-> Rules ()
-> Maybe (LanguageContextEnv Config)
-> Logger
-> Debouncer NormalizedUri
-> IdeOptions
-> WithHieDb
-> IndexQueue
-> IO IdeState
initialise Recorder (WithPriority Log)
recorder Config
defaultConfig Rules ()
mainRule Maybe (LanguageContextEnv Config)
lspEnv Logger
logger Debouncer NormalizedUri
debouncer IdeOptions
options WithHieDb
withHieDb IndexQueue
hiedbChan = do
    Maybe String
shakeProfiling <- do
        let fromConf :: Maybe String
fromConf = IdeOptions -> Maybe String
optShakeProfiling IdeOptions
options
        Maybe String
fromEnv <- String -> IO (Maybe String)
lookupEnv String
"GHCIDE_BUILD_PROFILING"
        Maybe String -> IO (Maybe String)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe String -> IO (Maybe String))
-> Maybe String -> IO (Maybe String)
forall a b. (a -> b) -> a -> b
$ Maybe String
fromConf Maybe String -> Maybe String -> Maybe String
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe String
fromEnv
    Recorder (WithPriority Log)
-> Maybe (LanguageContextEnv Config)
-> Config
-> Logger
-> Debouncer NormalizedUri
-> Maybe String
-> IdeReportProgress
-> IdeTesting
-> WithHieDb
-> IndexQueue
-> ShakeOptions
-> Rules ()
-> IO IdeState
shakeOpen
        ((Log -> Log)
-> Recorder (WithPriority Log) -> Recorder (WithPriority Log)
forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogShake Recorder (WithPriority Log)
recorder)
        Maybe (LanguageContextEnv Config)
lspEnv
        Config
defaultConfig
        Logger
logger
        Debouncer NormalizedUri
debouncer
        Maybe String
shakeProfiling
        (IdeOptions -> IdeReportProgress
optReportProgress IdeOptions
options)
        (IdeOptions -> IdeTesting
optTesting IdeOptions
options)
        WithHieDb
withHieDb
        IndexQueue
hiedbChan
        (IdeOptions -> ShakeOptions
optShakeOptions IdeOptions
options)
          (Rules () -> IO IdeState) -> Rules () -> IO IdeState
forall a b. (a -> b) -> a -> b
$ do
            GlobalIdeOptions -> Rules ()
forall a. IsIdeGlobal a => a -> Rules ()
addIdeGlobal (GlobalIdeOptions -> Rules ()) -> GlobalIdeOptions -> Rules ()
forall a b. (a -> b) -> a -> b
$ IdeOptions -> GlobalIdeOptions
GlobalIdeOptions IdeOptions
options
            Recorder (WithPriority Log) -> Rules ()
ofInterestRules ((Log -> Log)
-> Recorder (WithPriority Log) -> Recorder (WithPriority Log)
forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogOfInterest Recorder (WithPriority Log)
recorder)
            Recorder (WithPriority Log)
-> Maybe (LanguageContextEnv Config) -> Rules ()
fileExistsRules ((Log -> Log)
-> Recorder (WithPriority Log) -> Recorder (WithPriority Log)
forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogFileExists Recorder (WithPriority Log)
recorder) Maybe (LanguageContextEnv Config)
lspEnv
            Rules ()
mainRule

-- | Shutdown the Compiler Service.
shutdown :: IdeState -> IO ()
shutdown :: IdeState -> IO ()
shutdown = IdeState -> IO ()
shakeShut

-- This will return as soon as the result of the action is
-- available.  There might still be other rules running at this point,
-- e.g., the ofInterestRule.
runAction :: String -> IdeState -> Action a -> IO a
runAction :: String -> IdeState -> Action a -> IO a
runAction String
herald IdeState
ide Action a
act =
  IO (IO a) -> IO a
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO a) -> IO a) -> IO (IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> DelayedAction a -> IO (IO a)
forall a. ShakeExtras -> DelayedAction a -> IO (IO a)
shakeEnqueue (IdeState -> ShakeExtras
shakeExtras IdeState
ide) (String -> Priority -> Action a -> DelayedAction a
forall a. String -> Priority -> Action a -> DelayedAction a
mkDelayedAction String
herald Priority
Logger.Debug Action a
act)