Skip to content

Commit 54b253a

Browse files
committed
Add PluginFileType
1 parent af1141c commit 54b253a

File tree

4 files changed

+40
-20
lines changed

4 files changed

+40
-20
lines changed

ghcide/src/Development/IDE/Core/Shake.hs

Lines changed: 2 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -168,7 +168,8 @@ import Ide.Plugin.Config
168168
import qualified Ide.PluginUtils as HLS
169169
import Ide.Types (IdePlugins (IdePlugins),
170170
PluginDescriptor (pluginId),
171-
PluginId)
171+
PluginId, SourceFileOrigin(..),
172+
getSourceFileOrigin)
172173
import Language.LSP.Diagnostics
173174
import Language.LSP.Protocol.Message
174175
import Language.LSP.Protocol.Types
@@ -1128,17 +1129,6 @@ defineEarlyCutOffNoFile recorder f = defineEarlyCutoff recorder $ RuleNoDiagnost
11281129
if file == emptyFilePath then do (hash, res) <- f k; return (Just hash, Just res) else
11291130
fail $ "Rule " ++ show k ++ " should always be called with the empty string for a file"
11301131

1131-
data SourceFileOrigin = FromProject | FromDependency
1132-
1133-
getSourceFileOrigin :: NormalizedFilePath -> SourceFileOrigin
1134-
getSourceFileOrigin f =
1135-
case [".hls", "dependencies"] `isInfixOf` (splitDirectories file) of
1136-
True -> FromDependency
1137-
False -> FromProject
1138-
where
1139-
file :: FilePath
1140-
file = fromNormalizedFilePath f
1141-
11421132
defineEarlyCutoff'
11431133
:: forall k v. IdeRule k v
11441134
=> (Maybe Int32 -> [FileDiagnostic] -> Action ()) -- ^ update diagnostics

ghcide/src/Development/IDE/LSP/Notifications.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -158,6 +158,7 @@ descriptor recorder plId = (defaultPluginDescriptor plId) { pluginNotificationHa
158158
-- The ghcide descriptors should come last'ish so that the notification handlers
159159
-- (which restart the Shake build) run after everything else
160160
pluginPriority = ghcideNotificationsPluginPriority
161+
, pluginFileType = PluginFileType [FromProject, FromDependency] defaultPluginFileExtensions
161162
}
162163

163164
ghcideNotificationsPluginPriority :: Natural

ghcide/src/Development/IDE/Plugin/HLS/GhcIde.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -53,9 +53,10 @@ descriptor plId = (defaultPluginDescriptor plId)
5353
<> mkPluginHandler SMethod_TextDocumentDocumentHighlight (\ide _ DocumentHighlightParams{..} ->
5454
documentHighlight ide TextDocumentPositionParams{..})
5555
<> mkPluginHandler SMethod_TextDocumentReferences (\ide _ params -> references ide params)
56-
<> mkPluginHandler SMethod_WorkspaceSymbol (\ide _ params -> fmap InL <$> wsSymbols ide params),
56+
<> mkPluginHandler SMethod_WorkspaceSymbol (\ide _ params -> fmap InL <$> wsSymbols ide params)
5757

58-
pluginConfigDescriptor = defaultConfigDescriptor
58+
, pluginConfigDescriptor = defaultConfigDescriptor
59+
, pluginFileType = PluginFileType [FromProject, FromDependency] defaultPluginFileExtensions
5960
}
6061

6162
-- ---------------------------------------------------------------------

hls-plugin-api/src/Ide/Types.hs

Lines changed: 34 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@
2424
{-# LANGUAGE ViewPatterns #-}
2525
module Ide.Types
2626
( PluginDescriptor(..), defaultPluginDescriptor, defaultCabalPluginDescriptor
27-
, defaultPluginPriority
27+
, defaultPluginPriority, defaultPluginFileExtensions
2828
, IdeCommand(..)
2929
, IdeMethod(..)
3030
, IdeNotification(..)
@@ -37,6 +37,7 @@ module Ide.Types
3737
, FormattingType(..), FormattingMethod, FormattingHandler, mkFormattingHandlers
3838
, HasTracing(..)
3939
, PluginCommand(..), CommandId(..), CommandFunction, mkLspCommand, mkLspCmdId
40+
, PluginFileType(..)
4041
, PluginId(..)
4142
, PluginHandler(..), mkPluginHandler
4243
, PluginHandlers(..)
@@ -45,6 +46,8 @@ module Ide.Types
4546
, PluginNotificationHandler(..), mkPluginNotificationHandler
4647
, PluginNotificationHandlers(..)
4748
, PluginRequestMethod(..)
49+
, SourceFileOrigin(..)
50+
, getSourceFileOrigin
4851
, getProcessID, getPid
4952
, installSigUsr1Handler
5053
, responseError
@@ -73,6 +76,7 @@ import Data.GADT.Compare
7376
import Data.Hashable (Hashable)
7477
import Data.HashMap.Strict (HashMap)
7578
import qualified Data.HashMap.Strict as HashMap
79+
import Data.List (isInfixOf)
7680
import Data.List.Extra (find, sortOn)
7781
import Data.List.NonEmpty (NonEmpty (..), toList)
7882
import qualified Data.Map as Map
@@ -268,23 +272,44 @@ data PluginDescriptor (ideState :: *) =
268272
, pluginNotificationHandlers :: PluginNotificationHandlers ideState
269273
, pluginModifyDynflags :: DynFlagsModifications
270274
, pluginCli :: Maybe (ParserInfo (IdeCommand ideState))
271-
, pluginFileType :: [T.Text]
275+
, pluginFileType :: PluginFileType
272276
-- ^ File extension of the files the plugin is responsible for.
273277
-- The plugin is only allowed to handle files with these extensions.
274278
-- When writing handlers, etc. for this plugin it can be assumed that all handled files are of this type.
275279
-- The file extension must have a leading '.'.
276280
}
277281

282+
data PluginFileType = PluginFileType [SourceFileOrigin] [T.Text]
283+
284+
data SourceFileOrigin = FromProject | FromDependency deriving Eq
285+
286+
getSourceFileOrigin :: NormalizedFilePath -> SourceFileOrigin
287+
getSourceFileOrigin f =
288+
case [".hls", "dependencies"] `isInfixOf` (splitDirectories file) of
289+
True -> FromDependency
290+
False -> FromProject
291+
where
292+
file :: FilePath
293+
file = fromNormalizedFilePath f
294+
278295
-- | Check whether the given plugin descriptor is responsible for the file with the given path.
279296
-- Compares the file extension of the file at the given path with the file extension
280297
-- the plugin is responsible for.
281298
pluginResponsible :: Uri -> PluginDescriptor c -> Bool
282299
pluginResponsible uri pluginDesc
283300
| Just fp <- mfp
284-
, T.pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
301+
, checkFile (pluginFileType pluginDesc) fp = True
285302
| otherwise = False
286303
where
287-
mfp = uriToFilePath uri
304+
checkFile :: PluginFileType -> NormalizedFilePath -> Bool
305+
checkFile (PluginFileType validOrigins validExtensions) fp =
306+
getSourceFileOrigin fp `elem` validOrigins
307+
&&
308+
getExtension fp `elem` validExtensions
309+
getExtension :: NormalizedFilePath -> T.Text
310+
getExtension = T.pack . takeExtension . fromNormalizedFilePath
311+
mfp :: Maybe NormalizedFilePath
312+
mfp = uriToNormalizedFilePath $ toNormalizedUri uri
288313

289314
-- | An existential wrapper of 'Properties'
290315
data CustomConfig = forall r. CustomConfig (Properties r)
@@ -852,7 +877,10 @@ defaultPluginDescriptor plId =
852877
mempty
853878
mempty
854879
Nothing
855-
[".hs", ".lhs", ".hs-boot"]
880+
(PluginFileType [FromProject] defaultPluginFileExtensions)
881+
882+
defaultPluginFileExtensions :: [T.Text]
883+
defaultPluginFileExtensions = [".hs", ".lhs", ".hs-boot"]
856884

857885
-- | Set up a plugin descriptor, initialized with default values.
858886
-- This plugin descriptor is prepared for @.cabal@ files and as such,
@@ -872,7 +900,7 @@ defaultCabalPluginDescriptor plId =
872900
mempty
873901
mempty
874902
Nothing
875-
[".cabal"]
903+
(PluginFileType [FromProject] [".cabal"])
876904

877905
newtype CommandId = CommandId T.Text
878906
deriving (Show, Read, Eq, Ord)

0 commit comments

Comments
 (0)