24
24
{-# LANGUAGE ViewPatterns #-}
25
25
module Ide.Types
26
26
( PluginDescriptor (.. ), defaultPluginDescriptor, defaultCabalPluginDescriptor
27
- , defaultPluginPriority
27
+ , defaultPluginPriority, defaultPluginFileExtensions
28
28
, IdeCommand (.. )
29
29
, IdeMethod (.. )
30
30
, IdeNotification (.. )
@@ -37,6 +37,7 @@ module Ide.Types
37
37
, FormattingType (.. ), FormattingMethod , FormattingHandler , mkFormattingHandlers
38
38
, HasTracing (.. )
39
39
, PluginCommand (.. ), CommandId (.. ), CommandFunction , mkLspCommand, mkLspCmdId
40
+ , PluginFileType (.. )
40
41
, PluginId (.. )
41
42
, PluginHandler (.. ), mkPluginHandler
42
43
, PluginHandlers (.. )
@@ -45,6 +46,8 @@ module Ide.Types
45
46
, PluginNotificationHandler (.. ), mkPluginNotificationHandler
46
47
, PluginNotificationHandlers (.. )
47
48
, PluginRequestMethod (.. )
49
+ , SourceFileOrigin (.. )
50
+ , getSourceFileOrigin
48
51
, getProcessID, getPid
49
52
, installSigUsr1Handler
50
53
, responseError
@@ -73,6 +76,7 @@ import Data.GADT.Compare
73
76
import Data.Hashable (Hashable )
74
77
import Data.HashMap.Strict (HashMap )
75
78
import qualified Data.HashMap.Strict as HashMap
79
+ import Data.List (isInfixOf )
76
80
import Data.List.Extra (find , sortOn )
77
81
import Data.List.NonEmpty (NonEmpty (.. ), toList )
78
82
import qualified Data.Map as Map
@@ -268,23 +272,44 @@ data PluginDescriptor (ideState :: *) =
268
272
, pluginNotificationHandlers :: PluginNotificationHandlers ideState
269
273
, pluginModifyDynflags :: DynFlagsModifications
270
274
, pluginCli :: Maybe (ParserInfo (IdeCommand ideState ))
271
- , pluginFileType :: [ T. Text ]
275
+ , pluginFileType :: PluginFileType
272
276
-- ^ File extension of the files the plugin is responsible for.
273
277
-- The plugin is only allowed to handle files with these extensions.
274
278
-- When writing handlers, etc. for this plugin it can be assumed that all handled files are of this type.
275
279
-- The file extension must have a leading '.'.
276
280
}
277
281
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
+
278
295
-- | Check whether the given plugin descriptor is responsible for the file with the given path.
279
296
-- Compares the file extension of the file at the given path with the file extension
280
297
-- the plugin is responsible for.
281
298
pluginResponsible :: Uri -> PluginDescriptor c -> Bool
282
299
pluginResponsible uri pluginDesc
283
300
| Just fp <- mfp
284
- , T. pack (takeExtension fp) `elem` pluginFileType pluginDesc = True
301
+ , checkFile ( pluginFileType pluginDesc) fp = True
285
302
| otherwise = False
286
303
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
288
313
289
314
-- | An existential wrapper of 'Properties'
290
315
data CustomConfig = forall r . CustomConfig (Properties r )
@@ -852,7 +877,10 @@ defaultPluginDescriptor plId =
852
877
mempty
853
878
mempty
854
879
Nothing
855
- [" .hs" , " .lhs" , " .hs-boot" ]
880
+ (PluginFileType [FromProject ] defaultPluginFileExtensions)
881
+
882
+ defaultPluginFileExtensions :: [T. Text ]
883
+ defaultPluginFileExtensions = [" .hs" , " .lhs" , " .hs-boot" ]
856
884
857
885
-- | Set up a plugin descriptor, initialized with default values.
858
886
-- This plugin descriptor is prepared for @.cabal@ files and as such,
@@ -872,7 +900,7 @@ defaultCabalPluginDescriptor plId =
872
900
mempty
873
901
mempty
874
902
Nothing
875
- [ " .cabal" ]
903
+ ( PluginFileType [ FromProject ] [ " .cabal" ])
876
904
877
905
newtype CommandId = CommandId T. Text
878
906
deriving (Show , Read , Eq , Ord )
0 commit comments