@@ -18,43 +18,49 @@ module Ide.Plugin.Cabal.CabalAdd
18
18
where
19
19
20
20
import Control.Monad (filterM , void )
21
- import Control.Monad.IO.Class (liftIO , MonadIO )
21
+ import Control.Monad.IO.Class (MonadIO , liftIO )
22
22
import Data.String (IsString )
23
23
import qualified Data.Text as T
24
24
import qualified Data.Text.Encoding as T
25
- import Development.IDE (IdeState (shakeExtras ),
26
- runIdeAction ,
25
+ import Development.IDE (IdeState ,
27
26
useWithStale )
28
27
import Distribution.PackageDescription.Quirks (patchQuirks )
29
28
import Ide.PluginUtils (WithDeletions (SkipDeletions ),
30
29
diffText ,
31
30
mkLspCommand )
32
31
import Ide.Types (CommandFunction ,
33
32
CommandId (CommandId ),
34
- PluginId , pluginGetClientCapabilities , pluginSendRequest , HandlerM )
35
- import Language.LSP.Protocol.Types (CodeAction (CodeAction ),
33
+ HandlerM ,
34
+ PluginId ,
35
+ pluginGetClientCapabilities ,
36
+ pluginSendRequest )
37
+ import Language.LSP.Protocol.Types (ApplyWorkspaceEditParams (ApplyWorkspaceEditParams ),
38
+ ClientCapabilities ,
39
+ CodeAction (CodeAction ),
36
40
CodeActionKind (CodeActionKind_QuickFix ),
37
41
Diagnostic (.. ),
38
42
Null (Null ),
39
- TextDocumentIdentifier ,
40
43
VersionedTextDocumentIdentifier ,
41
44
WorkspaceEdit ,
42
- WorkspaceFoldersServerCapabilities ,
43
45
toNormalizedFilePath ,
44
- type (|? ) (InR ), ClientCapabilities , ApplyWorkspaceEditParams ( ApplyWorkspaceEditParams ) )
46
+ type (|? ) (InR ))
45
47
import System.Directory (doesFileExist ,
46
48
listDirectory )
47
49
50
+ import Control.Monad.Trans.Class (lift )
51
+ import Control.Monad.Trans.Except
48
52
import Data.Aeson.Types (FromJSON ,
49
53
ToJSON , toJSON )
50
54
import Data.ByteString (ByteString )
51
55
import qualified Data.ByteString.Char8 as B
52
56
import Data.List.NonEmpty (NonEmpty (.. ),
53
57
fromList )
58
+ import Data.Text.Encoding (encodeUtf8 )
54
59
import Development.IDE.Core.Rules (runAction )
60
+ import Development.IDE.Core.RuleTypes (GetFileContents (.. ))
55
61
import Distribution.Client.Add as Add
56
62
import Distribution.Compat.Prelude (Generic )
57
- import Distribution.PackageDescription (GenericPackageDescription ( GenericPackageDescription ) ,
63
+ import Distribution.PackageDescription (GenericPackageDescription ,
58
64
packageDescription ,
59
65
specVersion )
60
66
import Distribution.PackageDescription.Configuration (flattenPackageDescription )
@@ -65,25 +71,19 @@ import Distribution.Simple.BuildTarget (BuildTarget,
65
71
import Distribution.Simple.Utils (safeHead )
66
72
import Distribution.Verbosity (silent ,
67
73
verboseNoStderr )
74
+ import qualified Ide.Logger as Logger
68
75
import Ide.Plugin.Cabal.Completion.Types (ParseCabalFields (.. ),
69
76
ParseCabalFile (.. ))
77
+ import Ide.Plugin.Cabal.Orphans ()
78
+ import Ide.Plugin.Error
79
+ import Language.LSP.Protocol.Message (SMethod (SMethod_WorkspaceApplyEdit ))
70
80
import System.FilePath (dropFileName ,
71
81
makeRelative ,
72
82
splitPath ,
73
83
takeExtension ,
74
84
(</>) )
75
85
import Text.PrettyPrint (render )
76
86
import Text.Regex.TDFA
77
- import Development.IDE.Core.RuleTypes (GetFileContents (.. ))
78
- import Data.Text.Encoding (encodeUtf8 )
79
- import Ide.Plugin.Cabal.Orphans ()
80
- import Distribution.Fields.Field (fieldAnn )
81
- import Control.Monad.Trans.Class (lift )
82
- import Language.LSP.Protocol.Message (SMethod (SMethod_WorkspaceApplyEdit ))
83
- import Debug.Trace
84
- import qualified Ide.Logger as Logger
85
- import Control.Monad.Trans.Except
86
- import Ide.Plugin.Error
87
87
88
88
data Log
89
89
= LogFoundResponsibleCabalFile FilePath
@@ -101,24 +101,6 @@ instance Logger.Pretty Log where
101
101
LogCreatedEdit edit -> " Created inplace edit:\n " Logger. <+> Logger. pretty edit
102
102
LogExecutedCommand -> " Executed CabalAdd command"
103
103
104
- -- | Given a path to a haskell file, returns the closest cabal file.
105
- -- If cabal file wasn't found, dives Nothing.
106
- findResponsibleCabalFile :: FilePath -> IO (Maybe FilePath )
107
- findResponsibleCabalFile haskellFilePath = do
108
- let dirPath = dropFileName haskellFilePath
109
- allDirPaths = reverse $ scanl1 (</>) (splitPath dirPath) -- sorted from most to least specific
110
- go allDirPaths
111
- where
112
- go [] = pure Nothing
113
- go (path: ps) = do
114
- objects <- listDirectory path
115
- let objectsWithPaths = map (\ obj -> path <> obj) objects
116
- objectsCabalExtension = filter (\ c -> takeExtension c == " .cabal" ) objectsWithPaths
117
- cabalFiles <- filterM (\ c -> doesFileExist c) objectsCabalExtension
118
- case safeHead cabalFiles of
119
- Nothing -> go ps
120
- Just cabalFile -> pure $ Just cabalFile
121
-
122
104
123
105
-- | Gives a code action that calls the command,
124
106
-- if a suggestion for a missing dependency is found.
@@ -134,6 +116,13 @@ hiddenPackageAction recorder plId verTxtDocId maxCompletions diag haskellFilePat
134
116
hiddenPackageSuggestion maxCompletions (_message diag) | target <- targets]
135
117
where
136
118
buildTargetToStringRepr target = render $ pretty $ buildTargetComponentName target
119
+
120
+ getBuildTargets :: GenericPackageDescription -> FilePath -> FilePath -> IO [BuildTarget ]
121
+ getBuildTargets gpd cabalFilePath haskellFilePath = do
122
+ let haskellFileRelativePath = makeRelative (dropFileName cabalFilePath) haskellFilePath
123
+ readBuildTargets (verboseNoStderr silent) (flattenPackageDescription gpd) [haskellFileRelativePath]
124
+
125
+ mkCodeAction :: FilePath -> Maybe String -> (T. Text , T. Text ) -> CodeAction
137
126
mkCodeAction cabalFilePath target (suggestedDep, suggestedVersion) =
138
127
let
139
128
versionTitle = if T. null suggestedVersion then T. empty else " version " <> suggestedVersion
@@ -200,36 +189,19 @@ command recorder state _ params@(CabalAddCommandParams {cabalPath = path, verTxt
200
189
Logger. logWith recorder Logger. Info LogExecutedCommand
201
190
pure $ InR Null
202
191
203
-
204
- -- | Gives cabal file's contents or throws error.
205
- -- Inspired by @readCabalFile@ in cabal-add,
206
- -- Distribution.Client.Main
207
- readCabalFile :: MonadIO m => FilePath -> ExceptT PluginError m ByteString
208
- readCabalFile fileName = do
209
- cabalFileExists <- liftIO $ doesFileExist fileName
210
- if cabalFileExists
211
- then snd . patchQuirks <$> liftIO (B. readFile fileName)
212
- else throwE $ PluginInternalError $ T. pack (" Failed to read cabal file at " <> fileName)
213
-
214
- getBuildTargets :: GenericPackageDescription -> FilePath -> FilePath -> IO [BuildTarget ]
215
- getBuildTargets gpd cabalFilePath haskellFilePath = do
216
- let haskellFileRelativePath = makeRelative (dropFileName cabalFilePath) haskellFilePath
217
- readBuildTargets (verboseNoStderr silent) (flattenPackageDescription gpd) [haskellFileRelativePath]
218
-
219
-
220
192
-- | Constructs prerequisets for the @executeConfig@
221
193
-- and runs it, given path to the cabal file and a dependency message.
222
- --
194
+ -- Given the new contents of the cabal file constructs and returns the @edit@.
223
195
-- Inspired by @main@ in cabal-add,
224
196
-- Distribution.Client.Main
225
197
getDependencyEdit :: MonadIO m => Logger. Recorder (Logger. WithPriority Log ) -> (IdeState , ClientCapabilities , VersionedTextDocumentIdentifier ) ->
226
198
FilePath -> Maybe String -> NonEmpty String -> ExceptT PluginError m WorkspaceEdit
227
199
getDependencyEdit recorder env cabalFilePath buildTarget dependency = do
228
200
let (state, caps, verTxtDocId) = env
229
201
(mbCnfOrigContents, mbFields, mbPackDescr) <- liftIO $ runAction " cabal.cabal-add" state $ do
230
- contents <- useWithStale GetFileContents $ toNormalizedFilePath cabalFilePath
231
- inFields <- useWithStale ParseCabalFields $ toNormalizedFilePath cabalFilePath
232
- inPackDescr <- useWithStale ParseCabalFile $ toNormalizedFilePath cabalFilePath
202
+ contents <- Development.IDE. useWithStale GetFileContents $ toNormalizedFilePath cabalFilePath
203
+ inFields <- Development.IDE. useWithStale ParseCabalFields $ toNormalizedFilePath cabalFilePath
204
+ inPackDescr <- Development.IDE. useWithStale ParseCabalFile $ toNormalizedFilePath cabalFilePath
233
205
let mbCnfOrigContents = case snd . fst <$> contents of
234
206
Just (Just txt) -> Just $ encodeUtf8 txt
235
207
_ -> Nothing
@@ -240,7 +212,7 @@ getDependencyEdit recorder env cabalFilePath buildTarget dependency = do
240
212
(cnfOrigContents, fields, packDescr) <- do
241
213
cnfOrigContents <- case mbCnfOrigContents of
242
214
(Just cnfOrigContents) -> pure cnfOrigContents
243
- Nothing -> readCabalFile cabalFilePath
215
+ Nothing -> readCabalFile cabalFilePath
244
216
(fields, packDescr) <- case (mbFields, mbPackDescr) of
245
217
(Just fields, Just packDescr) -> pure (fields, packDescr)
246
218
(_, _) -> case parseCabalFile cabalFilePath cnfOrigContents of
@@ -256,7 +228,7 @@ getDependencyEdit recorder env cabalFilePath buildTarget dependency = do
256
228
pure (fields, packDescr, cmp, deps)
257
229
258
230
(cnfFields, origPackDescr, cnfComponent, cnfDependencies) <- case inputs of
259
- Left err -> throwE $ PluginInternalError $ T. pack $ err
231
+ Left err -> throwE $ PluginInternalError $ T. pack err
260
232
Right pair -> pure pair
261
233
262
234
case executeConfig (validateChanges origPackDescr) (Config {.. }) of
@@ -265,3 +237,31 @@ getDependencyEdit recorder env cabalFilePath buildTarget dependency = do
265
237
let edit = diffText caps (verTxtDocId, T. decodeUtf8 cnfOrigContents) (T. decodeUtf8 newContents) SkipDeletions
266
238
Logger. logWith recorder Logger. Info $ LogCreatedEdit edit
267
239
pure edit
240
+
241
+ -- | Given a path to a haskell file, returns the closest cabal file.
242
+ -- If cabal file wasn't found, dives Nothing.
243
+ findResponsibleCabalFile :: FilePath -> IO (Maybe FilePath )
244
+ findResponsibleCabalFile haskellFilePath = do
245
+ let dirPath = dropFileName haskellFilePath
246
+ allDirPaths = reverse $ scanl1 (</>) (splitPath dirPath) -- sorted from most to least specific
247
+ go allDirPaths
248
+ where
249
+ go [] = pure Nothing
250
+ go (path: ps) = do
251
+ objects <- listDirectory path
252
+ let objectsWithPaths = map (\ obj -> path <> obj) objects
253
+ objectsCabalExtension = filter (\ c -> takeExtension c == " .cabal" ) objectsWithPaths
254
+ cabalFiles <- filterM (\ c -> doesFileExist c) objectsCabalExtension
255
+ case safeHead cabalFiles of
256
+ Nothing -> go ps
257
+ Just cabalFile -> pure $ Just cabalFile
258
+
259
+ -- | Gives cabal file's contents or throws error.
260
+ -- Inspired by @readCabalFile@ in cabal-add,
261
+ -- Distribution.Client.Main
262
+ readCabalFile :: MonadIO m => FilePath -> ExceptT PluginError m ByteString
263
+ readCabalFile fileName = do
264
+ cabalFileExists <- liftIO $ doesFileExist fileName
265
+ if cabalFileExists
266
+ then snd . patchQuirks <$> liftIO (B. readFile fileName)
267
+ else throwE $ PluginInternalError $ T. pack (" Failed to read cabal file at " <> fileName)
0 commit comments