|
| 1 | +module Development.IDE.Core.PluginUtils where |
| 2 | + |
| 3 | +import Control.Monad.Extra |
| 4 | +import Control.Monad.IO.Class |
| 5 | +import Control.Monad.Trans.Except |
| 6 | +import Control.Monad.Trans.Maybe |
| 7 | +import Data.Functor.Identity |
| 8 | +import Development.IDE.Core.PositionMapping |
| 9 | +import Development.IDE.Core.Shake (IdeAction, IdeRule, |
| 10 | + IdeState (shakeExtras), |
| 11 | + mkDelayedAction, |
| 12 | + shakeEnqueue) |
| 13 | +import qualified Development.IDE.Core.Shake as Shake |
| 14 | +import Development.IDE.GHC.Orphans () |
| 15 | +import Development.IDE.Graph hiding (ShakeValue) |
| 16 | +import Development.IDE.Types.Location (NormalizedFilePath) |
| 17 | +import qualified Development.IDE.Types.Location as Location |
| 18 | +import qualified Development.IDE.Types.Logger as Logger |
| 19 | +import Ide.PluginUtils (PluginError (..)) |
| 20 | +import Data.Either.Extra (maybeToEither) |
| 21 | +import qualified Language.LSP.Types as LSP |
| 22 | + |
| 23 | +runAction :: MonadIO m => String -> IdeState -> ExceptT e Action a -> ExceptT e m a |
| 24 | +runAction herald ide act = |
| 25 | + hoistExceptT . ExceptT $ join $ shakeEnqueue (shakeExtras ide) (mkDelayedAction herald Logger.Debug $ runExceptT act) |
| 26 | + |
| 27 | +useWithStaleT :: IdeRule k v |
| 28 | + => k -> NormalizedFilePath -> MaybeT Action (v, PositionMapping) |
| 29 | +useWithStaleT key file = MaybeT $ runIdentity <$> Shake.usesWithStale key (Identity file) |
| 30 | + |
| 31 | +-- | Request a Rule result, it not available return the last computed result which may be stale. |
| 32 | +-- Errors out if none available. |
| 33 | +useWithStale_ ::(IdeRule k v) |
| 34 | + => k -> NormalizedFilePath -> ExceptT e Action (v, PositionMapping) |
| 35 | +useWithStale_ key file = ExceptT $ fmap Right $ Shake.useWithStale_ key file |
| 36 | + |
| 37 | +useWithStale :: IdeRule k v |
| 38 | + => k -> NormalizedFilePath -> ExceptT PluginError Action (v, PositionMapping) |
| 39 | +useWithStale key file = maybeToExceptT PluginTemporarilyUnresponsive $ useWithStaleT key file |
| 40 | + |
| 41 | +-- | useE is useful to implement functions that aren’t rules but need shortcircuiting |
| 42 | +-- e.g. getDefinition. |
| 43 | +use :: IdeRule k v => k -> NormalizedFilePath -> ExceptT PluginError Action v |
| 44 | +use k = maybeToExceptT PluginTemporarilyUnresponsive . MaybeT . Shake.use k |
| 45 | + |
| 46 | +-- | useE is useful to implement functions that aren’t rules but need shortcircuiting |
| 47 | +-- e.g. getDefinition. |
| 48 | +useE :: IdeRule k v => k -> NormalizedFilePath -> ExceptT PluginError IdeAction (v, PositionMapping) |
| 49 | +useE k = maybeToExceptT PluginTemporarilyUnresponsive . MaybeT . Shake.useWithStaleFast k |
| 50 | + |
| 51 | +hoistExceptT :: MonadIO m => ExceptT e IO a -> ExceptT e m a |
| 52 | +hoistExceptT = ExceptT . liftIO . runExceptT |
| 53 | + |
| 54 | +hoistAction :: Action a -> ExceptT e Action a |
| 55 | +hoistAction = ExceptT . fmap Right |
| 56 | + |
| 57 | +uriToFilePath' :: Monad m => LSP.Uri -> ExceptT PluginError m FilePath |
| 58 | +uriToFilePath' uri = ExceptT . pure . maybeToEither (PluginUriToFilePath uri) $ Location.uriToFilePath' uri |
0 commit comments