|
| 1 | +{-# LANGUAGE AllowAmbiguousTypes #-} |
| 2 | +{-# LANGUAGE ExplicitNamespaces #-} |
| 3 | +{-# LANGUAGE FlexibleContexts #-} |
| 4 | +{-# LANGUAGE LambdaCase #-} |
| 5 | +{-# LANGUAGE OverloadedStrings #-} |
| 6 | +module Ide.Plugin.Cabal.FieldSuggest |
| 7 | +( fieldErrorSuggestion |
| 8 | +, fieldErrorAction |
| 9 | + -- * Re-exports |
| 10 | +, T.Text |
| 11 | +, Diagnostic(..) |
| 12 | +) |
| 13 | +where |
| 14 | + |
| 15 | +import qualified Data.HashMap.Strict as Map |
| 16 | +import qualified Data.Text as T |
| 17 | +import Language.LSP.Types (CodeAction (CodeAction), |
| 18 | + CodeActionKind (CodeActionQuickFix), |
| 19 | + Diagnostic (..), List (List), |
| 20 | + Position (Position), Range (Range), |
| 21 | + TextEdit (TextEdit), Uri, |
| 22 | + WorkspaceEdit (WorkspaceEdit)) |
| 23 | +import Text.Regex.TDFA |
| 24 | + |
| 25 | +-- | Given a diagnostic returned by 'Ide.Plugin.Cabal.Diag.errorDiagnostic', |
| 26 | +-- if it represents an "Unknown field"-error along |
| 27 | +-- with a incorrect field, then return a 'CodeAction' for replacing the |
| 28 | +-- the incorrect field with the suggestion. |
| 29 | +-- It should be context sensitive, but for now it isn't |
| 30 | +fieldErrorAction |
| 31 | + :: Uri |
| 32 | + -- ^ File for which the diagnostic was generated |
| 33 | + -> Diagnostic |
| 34 | + -- ^ Output of 'Ide.Plugin.Cabal.Diag.errorDiagnostic' |
| 35 | + -> [CodeAction] |
| 36 | +fieldErrorAction uri diag = |
| 37 | + mkCodeAction <$> fieldErrorSuggestion diag |
| 38 | + where |
| 39 | + mkCodeAction (original, suggestion) = |
| 40 | + let |
| 41 | + -- Range returned by cabal here represents fragment from start of |
| 42 | + -- offending identifier to end of line, we modify it to the end of identifier |
| 43 | + adjustRange (Range rangeFrom@(Position line col) _) = |
| 44 | + Range rangeFrom (Position line (col + fromIntegral (T.length original))) |
| 45 | + title = "Replace with " <> suggestion |
| 46 | + tedit = [TextEdit (adjustRange $ _range diag) suggestion] |
| 47 | + edit = WorkspaceEdit (Just $ Map.singleton uri $ List tedit) Nothing Nothing |
| 48 | + in CodeAction title (Just CodeActionQuickFix) (Just $ List []) Nothing Nothing (Just edit) Nothing Nothing |
| 49 | + |
| 50 | +-- | Given a diagnostic returned by 'Ide.Plugin.Cabal.Diag.errorDiagnostic', |
| 51 | +-- if it represents an "Unknown field"- error with incorrect identifier |
| 52 | +-- then return the suggestion (for now placeholder "name") |
| 53 | +-- along with the incorrect identifier. |
| 54 | +-- |
| 55 | +fieldErrorSuggestion |
| 56 | + :: Diagnostic |
| 57 | + -- ^ Output of 'Ide.Plugin.Cabal.Diag.errorDiagnostic' |
| 58 | + -> [(T.Text, T.Text)] |
| 59 | + -- ^ (Original (incorrect) license identifier, suggested replacement) |
| 60 | +fieldErrorSuggestion diag = |
| 61 | + mSuggestion (_message diag) >>= \case |
| 62 | + [original] -> [(original, "name")] |
| 63 | + _ -> [] |
| 64 | + where |
| 65 | + regex :: T.Text |
| 66 | + regex = "Unknown field: \"(.*)\"" |
| 67 | + mSuggestion msg = getMatch <$> (msg :: T.Text) =~~ regex |
| 68 | + getMatch :: (T.Text, T.Text, T.Text, [T.Text]) -> [T.Text] |
| 69 | + getMatch (_, _, _, results) = results |
0 commit comments