From 8c4081b1500021b0a4c8f62f9d6e024182855957 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jan=20Hr=C4=8Dek?= Date: Sun, 14 Apr 2024 08:13:27 +0200 Subject: [PATCH 1/5] Fix ghc and hlint warnings --- cabal.project | 5 ++++- lsp-test/lsp-test.cabal | 1 - lsp-test/src/Language/LSP/Test/Compat.hs | 3 +-- lsp-test/src/Language/LSP/Test/Decoding.hs | 3 +-- lsp-test/src/Language/LSP/Test/Files.hs | 11 +++------- lsp-test/src/Language/LSP/Test/Session.hs | 24 +++++++++++----------- lsp-types/lsp-types.cabal | 5 ----- lsp/lsp.cabal | 2 -- lsp/src/Language/LSP/Diagnostics.hs | 2 +- lsp/src/Language/LSP/Server/Control.hs | 5 ++--- lsp/src/Language/LSP/Server/Core.hs | 7 +++---- lsp/src/Language/LSP/Server/Processing.hs | 10 ++++----- lsp/test/VspSpec.hs | 2 -- 13 files changed, 31 insertions(+), 49 deletions(-) diff --git a/cabal.project b/cabal.project index 61f20c07..cf14afb4 100644 --- a/cabal.project +++ b/cabal.project @@ -10,12 +10,15 @@ test-show-details: direct benchmarks: True +package * + ghc-options: -Wunused-packages + package lsp flags: +demo package lsp-types -- This makes a big difference here as lsp-types - -- has very many independent modules + -- has very many independent modules ghc-options: -j4 -- We allow filepath-1.5, this lets us actually test it. There is no problem diff --git a/lsp-test/lsp-test.cabal b/lsp-test/lsp-test.cabal index 5a72ac5f..a53c6772 100644 --- a/lsp-test/lsp-test.cabal +++ b/lsp-test/lsp-test.cabal @@ -66,7 +66,6 @@ library , mtl >=2.2 && <2.4 , parser-combinators ^>=1.3 , process ^>=1.6 - , row-types ^>=1.0 , some ^>=1.0 , text >=1 && <2.2 , time >=1.10 && <1.13 diff --git a/lsp-test/src/Language/LSP/Test/Compat.hs b/lsp-test/src/Language/LSP/Test/Compat.hs index 144797d0..41ad04c9 100644 --- a/lsp-test/src/Language/LSP/Test/Compat.hs +++ b/lsp-test/src/Language/LSP/Test/Compat.hs @@ -1,7 +1,6 @@ {-# LANGUAGE CPP #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} -- For some reason ghc warns about not using -- Control.Monad.IO.Class but it's needed for @@ -103,7 +102,7 @@ cleanupProcess (mb_stdin, mb_stdout, mb_stderr, ph) = do return () where ignoreSigPipe = ignoreIOError ResourceVanished ePIPE ignorePermDenied = ignoreIOError PermissionDenied eACCES - + ignoreIOError :: IOErrorType -> Errno -> IO () -> IO () ignoreIOError ioErrorType errno = C.handle $ \e -> case e of diff --git a/lsp-test/src/Language/LSP/Test/Decoding.hs b/lsp-test/src/Language/LSP/Test/Decoding.hs index c8892dd5..76bd842d 100644 --- a/lsp-test/src/Language/LSP/Test/Decoding.hs +++ b/lsp-test/src/Language/LSP/Test/Decoding.hs @@ -10,7 +10,6 @@ import Data.Aeson import Data.Aeson.Types import Data.ByteString.Lazy.Char8 qualified as B import Data.Foldable -import Data.Functor.Const import Data.Functor.Product import Data.Maybe import Language.LSP.Protocol.Lens qualified as L @@ -82,7 +81,7 @@ decodeFromServerMsg reqMap bytes = unP $ parse p obj let (mm, newMap) = pickFromIxMap lid reqMap in case mm of Nothing -> Nothing - Just m -> Just $ (m, Pair m (Const newMap)) + Just m -> Just (m, Pair m (Const newMap)) unP (Success (FromServerMess m msg)) = (reqMap, FromServerMess m msg) unP (Success (FromServerRsp (Pair m (Const newMap)) msg)) = (newMap, FromServerRsp m msg) unP (Error e) = error $ "Error decoding " <> show obj <> " :" <> e diff --git a/lsp-test/src/Language/LSP/Test/Files.hs b/lsp-test/src/Language/LSP/Test/Files.hs index 78e5db0d..06f2842b 100644 --- a/lsp-test/src/Language/LSP/Test/Files.hs +++ b/lsp-test/src/Language/LSP/Test/Files.hs @@ -83,18 +83,13 @@ mapUris f event = swapDocumentChangeUri (InR (InR (InL renameFile))) = InR $ InR $ InL $ L.newUri .~ f (renameFile ^. L.newUri) $ renameFile swapDocumentChangeUri (InR (InR (InR deleteFile))) = InR $ InR $ InR $ swapUri id deleteFile in e - & L.changes . _Just %~ swapKeys f + & L.changes . _Just %~ M.mapKeys f & L.documentChanges . _Just . traversed %~ swapDocumentChangeUri - swapKeys :: (Uri -> Uri) -> M.Map Uri b -> M.Map Uri b - swapKeys f = M.foldlWithKey' (\acc k v -> M.insert (f k) v acc) M.empty - swapUri :: L.HasUri b Uri => Lens' a b -> a -> a - swapUri lens x = - let newUri = f (x ^. lens . L.uri) - in (lens . L.uri) .~ newUri $ x + swapUri lens = (lens . L.uri) %~ f - -- \| Transforms rootUri/rootPath. + -- Transforms rootUri/rootPath. transformInit :: InitializeParams -> InitializeParams transformInit x = let modifyRootPath p = diff --git a/lsp-test/src/Language/LSP/Test/Session.hs b/lsp-test/src/Language/LSP/Test/Session.hs index 9263b65f..73f9f284 100644 --- a/lsp-test/src/Language/LSP/Test/Session.hs +++ b/lsp-test/src/Language/LSP/Test/Session.hs @@ -118,13 +118,13 @@ data SessionConfig = SessionConfig -- with a 'mylang' key whose value is the actual config for the server. You -- can also include other config sections if your server may request those. , ignoreLogNotifications :: Bool - -- ^ Whether or not to ignore @window/showMessage@ and @window/logMessage@ notifications + -- ^ Whether or not to ignore @window/showMessage@ and @window/logMessage@ notifications -- from the server, defaults to True. , ignoreConfigurationRequests :: Bool -- ^ Whether or not to ignore @workspace/configuration@ requests from the server, -- defaults to True. , ignoreRegistrationRequests :: Bool - -- ^ Whether or not to ignore @client/registerCapability@ and @client/unregisterCapability@ + -- ^ Whether or not to ignore @client/registerCapability@ and @client/unregisterCapability@ -- requests from the server, defaults to True. , initialWorkspaceFolders :: Maybe [WorkspaceFolder] -- ^ The initial workspace folders to send in the @initialize@ request. @@ -247,7 +247,7 @@ runSessionMonad context state (Session session) = runReaderT (runStateT conduit curId <- getCurTimeoutId case msg of ServerMessage sMsg -> yield sMsg - TimeoutMessage tId -> when (curId == tId) $ lastReceivedMessage <$> get >>= throw . Timeout + TimeoutMessage tId -> when (curId == tId) $ get >>= throw . Timeout . lastReceivedMessage -- | An internal version of 'runSession' that allows for a custom handler to listen to the server. -- It also does not automatically send initialize and exit messages. @@ -338,7 +338,7 @@ updateStateC = awaitForever $ \msg -> do let requestedSections = mapMaybe (\i -> i ^? L.section . _Just) $ r ^. L.params . L.items let o = curLspConfig state -- check for each requested section whether we have it - let configsOrErrs = (flip fmap) requestedSections $ \section -> + let configsOrErrs = flip fmap requestedSections $ \section -> case o ^. at (fromString $ T.unpack section) of Just config -> Right config Nothing -> Left section @@ -347,9 +347,9 @@ updateStateC = awaitForever $ \msg -> do -- we have to return exactly the number of sections requested, so if we can't find all of them then that's an error sendMessage $ TResponseMessage "2.0" (Just $ r ^. L.id) $ - if null errs - then (Right configs) - else Left $ ResponseError (InL LSPErrorCodes_RequestFailed) ("No configuration for requested sections: " <> (T.pack $ show errs)) Nothing + if null errs + then Right configs + else Left $ ResponseError (InL LSPErrorCodes_RequestFailed) ("No configuration for requested sections: " <> T.pack (show errs)) Nothing _ -> pure () unless ( (ignoringLogNotifications state && isLogNotification msg) @@ -414,7 +414,7 @@ updateState (FromServerMess SMethod_WorkspaceApplyEdit r) = do -- First, prefer the versioned documentChanges field allChangeParams <- case r ^. L.params . L.edit . L.documentChanges of - Just (cs) -> do + Just cs -> do mapM_ (checkIfNeedsOpened . documentChangeUri) cs -- replace the user provided version numbers with the VFS ones + 1 -- (technically we should check that the user versions match the VFS ones) @@ -472,8 +472,8 @@ updateState (FromServerMess SMethod_WorkspaceApplyEdit r) = do -- TODO: move somewhere reusable editToChangeEvent :: TextEdit |? AnnotatedTextEdit -> TextDocumentContentChangeEvent - editToChangeEvent (InR e) = TextDocumentContentChangeEvent $ InL $ TextDocumentContentChangePartial { _range = (e ^. L.range) , _rangeLength = Nothing , _text = (e ^. L.newText) } - editToChangeEvent (InL e) = TextDocumentContentChangeEvent $ InL $ TextDocumentContentChangePartial { _range = (e ^. L.range) , _rangeLength = Nothing , _text = (e ^. L.newText) } + editToChangeEvent (InR e) = TextDocumentContentChangeEvent $ InL $ TextDocumentContentChangePartial { _range = e ^. L.range , _rangeLength = Nothing , _text = e ^. L.newText } + editToChangeEvent (InL e) = TextDocumentContentChangeEvent $ InL $ TextDocumentContentChangePartial { _range = e ^. L.range , _rangeLength = Nothing , _text = e ^. L.newText } getParamsFromDocumentChange :: DocumentChange -> Maybe DidChangeTextDocumentParams getParamsFromDocumentChange (InL textDocumentEdit) = getParamsFromTextDocumentEdit textDocumentEdit @@ -491,11 +491,11 @@ updateState (FromServerMess SMethod_WorkspaceApplyEdit r) = do textDocumentEdits uri edits = do vers <- textDocumentVersions uri - pure $ map (\(v, e) -> TextDocumentEdit (review _versionedTextDocumentIdentifier v) [InL e]) $ zip vers edits + pure $ zipWith (\v e -> TextDocumentEdit (review _versionedTextDocumentIdentifier v) [InL e]) vers edits getChangeParams uri edits = do edits <- textDocumentEdits uri (reverse edits) - pure $ catMaybes $ map getParamsFromTextDocumentEdit edits + pure $ mapMaybe getParamsFromTextDocumentEdit edits mergeParams :: [DidChangeTextDocumentParams] -> DidChangeTextDocumentParams mergeParams params = let events = concat (toList (map (toList . (^. L.contentChanges)) params)) diff --git a/lsp-types/lsp-types.cabal b/lsp-types/lsp-types.cabal index ae90700a..3b6fd89e 100644 --- a/lsp-types/lsp-types.cabal +++ b/lsp-types/lsp-types.cabal @@ -67,12 +67,10 @@ library , deepseq >=1.4 && <1.6 , Diff >=0.4 && <0.6 , dlist ^>=1.0 - , exceptions ^>=0.10 , hashable ^>=1.4 , indexed-traversable ^>=0.1 , indexed-traversable-instances ^>=0.1 , lens >=5.1 && <5.3 - , lens-aeson ^>=1.2 , mod ^>=0.2 , mtl >=2.2 && <2.4 , network-uri ^>=2.6 @@ -600,7 +598,6 @@ library lsp-types-quickcheck Language.LSP.Protocol.QuickCheck.Types build-depends: - , aeson >=2 , base >=4.11 && <5 , lsp-types , row-types @@ -608,7 +605,6 @@ library lsp-types-quickcheck , quickcheck-instances , generic-arbitrary , template-haskell - , text >=1 && <2.2 executable generator hs-source-dirs: generator @@ -659,7 +655,6 @@ test-suite lsp-types-test , network-uri , QuickCheck , quickcheck-instances - , row-types , text build-tool-depends: hspec-discover:hspec-discover diff --git a/lsp/lsp.cabal b/lsp/lsp.cabal index c2c7cb8c..2f5ddf30 100644 --- a/lsp/lsp.cabal +++ b/lsp/lsp.cabal @@ -68,7 +68,6 @@ library , mtl >=2.2 && <2.4 , prettyprinter ^>=1.7 , random ^>=1.2 - , row-types ^>=1.0 , sorted-list ^>=0.2.1 , stm ^>=2.5 , text >=1 && <2.2 @@ -129,7 +128,6 @@ test-suite lsp-test , containers , hspec , lsp - , row-types , sorted-list , text , text-rope diff --git a/lsp/src/Language/LSP/Diagnostics.hs b/lsp/src/Language/LSP/Diagnostics.hs index acf51f14..88170ef7 100644 --- a/lsp/src/Language/LSP/Diagnostics.hs +++ b/lsp/src/Language/LSP/Diagnostics.hs @@ -50,7 +50,7 @@ type DiagnosticsBySource = Map.Map (Maybe Text) (SL.SortedList J.Diagnostic) -- --------------------------------------------------------------------- partitionBySource :: [J.Diagnostic] -> DiagnosticsBySource -partitionBySource diags = Map.fromListWith mappend $ map (\d -> (J._source d, (SL.singleton d))) diags +partitionBySource diags = Map.fromListWith mappend $ map (\d -> (J._source d, SL.singleton d)) diags -- --------------------------------------------------------------------- diff --git a/lsp/src/Language/LSP/Server/Control.hs b/lsp/src/Language/LSP/Server/Control.hs index f1467690..283f6c05 100644 --- a/lsp/src/Language/LSP/Server/Control.hs +++ b/lsp/src/Language/LSP/Server/Control.hs @@ -1,4 +1,3 @@ -{-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} module Language.LSP.Server.Control ( @@ -180,9 +179,9 @@ ioLoop ioLogger logger clientIn serverDefinition vfs sendMsg = do go (parse parser remainder) parser = do - try contentType <|> (return ()) + try contentType <|> return () len <- contentLength - try contentType <|> (return ()) + try contentType <|> return () _ <- string _ONE_CRLF Attoparsec.take len diff --git a/lsp/src/Language/LSP/Server/Core.hs b/lsp/src/Language/LSP/Server/Core.hs index 723420b3..cd443b42 100644 --- a/lsp/src/Language/LSP/Server/Core.hs +++ b/lsp/src/Language/LSP/Server/Core.hs @@ -22,7 +22,6 @@ import Colog.Core ( import Control.Applicative import Control.Concurrent.Async import Control.Concurrent.Extra as C -import Control.Concurrent.MVar import Control.Concurrent.STM import Control.Exception qualified as E import Control.Lens (at, (^.), (^?), _Just) @@ -88,7 +87,7 @@ deriving instance (Show LspCoreLog) instance Pretty LspCoreLog where pretty (NewConfig config) = "LSP: set new config:" <+> prettyJSON config - pretty (ConfigurationNotSupported) = "LSP: not requesting configuration since the client does not support workspace/configuration" + pretty ConfigurationNotSupported = "LSP: not requesting configuration since the client does not support workspace/configuration" pretty (ConfigurationParseError settings err) = vsep [ "LSP: configuration parse error:" @@ -97,7 +96,7 @@ instance Pretty LspCoreLog where , prettyJSON settings ] pretty (BadConfigurationResponse err) = "LSP: error when requesting configuration: " <+> pretty err - pretty (WrongConfigSections sections) = "LSP: expected only one configuration section, got: " <+> (prettyJSON $ J.toJSON sections) + pretty (WrongConfigSections sections) = "LSP: expected only one configuration section, got: " <+> prettyJSON (J.toJSON sections) pretty (CantRegister m) = "LSP: can't register dynamically for:" <+> pretty m newtype LspT config m a = LspT {unLspT :: ReaderT (LanguageContextEnv config) m a} @@ -612,7 +611,7 @@ trySendRegistration logger method regOpts = do pure (Just $ RegistrationToken method regId) else do - logger <& (CantRegister SMethod_WorkspaceDidChangeConfiguration) `WithSeverity` Warning + logger <& CantRegister SMethod_WorkspaceDidChangeConfiguration `WithSeverity` Warning pure Nothing {- | Sends a @client/unregisterCapability@ request and removes the handler diff --git a/lsp/src/Language/LSP/Server/Processing.hs b/lsp/src/Language/LSP/Server/Processing.hs index c3d9158b..ce34d9e3 100644 --- a/lsp/src/Language/LSP/Server/Processing.hs +++ b/lsp/src/Language/LSP/Server/Processing.hs @@ -1,5 +1,4 @@ {-# LANGUAGE GADTs #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecursiveDo #-} @@ -47,7 +46,6 @@ import Data.IxMap import Data.List import Data.List.NonEmpty (NonEmpty (..)) import Data.Map.Strict qualified as Map -import Data.Monoid import Data.String (fromString) import Data.Text qualified as T import Data.Text.Lazy.Encoding qualified as TL @@ -127,7 +125,7 @@ initializeRequestHandler logger ServerDefinition{..} vfs sendFunc req = do sendResp $ makeResponseError (req ^. L.id) err pure Nothing handleErr (Right a) = pure $ Just a - flip E.catch (initializeErrorHandler $ sendResp . makeResponseError (req ^. L.id)) $ handleErr <=< runExceptT $ mdo + E.handle (initializeErrorHandler $ sendResp . makeResponseError (req ^. L.id)) $ handleErr <=< runExceptT $ mdo let p = req ^. L.params rootDir = getFirst $ @@ -136,7 +134,7 @@ initializeRequestHandler logger ServerDefinition{..} vfs sendFunc req = do [ p ^? L.rootUri . _L >>= uriToFilePath , p ^? L.rootPath . _Just . _L <&> T.unpack ] - clientCaps = (p ^. L.capabilities) + clientCaps = p ^. L.capabilities let initialWfs = case p ^. L.workspaceFolders of Just (InL xs) -> xs @@ -148,11 +146,11 @@ initializeRequestHandler logger ServerDefinition{..} vfs sendFunc req = do initialConfig <- case configObject of Just o -> case parseConfig defaultConfig o of Right newConfig -> do - liftIO $ logger <& (LspCore $ NewConfig o) `WithSeverity` Debug + liftIO $ logger <& LspCore (NewConfig o) `WithSeverity` Debug pure newConfig Left err -> do -- Warn not error here, since initializationOptions is pretty unspecified - liftIO $ logger <& (LspCore $ ConfigurationParseError o err) `WithSeverity` Warning + liftIO $ logger <& LspCore (ConfigurationParseError o err) `WithSeverity` Warning pure defaultConfig Nothing -> pure defaultConfig diff --git a/lsp/test/VspSpec.hs b/lsp/test/VspSpec.hs index 0d94430a..3f23f150 100644 --- a/lsp/test/VspSpec.hs +++ b/lsp/test/VspSpec.hs @@ -1,10 +1,8 @@ {-# LANGUAGE DuplicateRecordFields #-} -{-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} module VspSpec where -import Data.Row import Data.String import Data.Text qualified as T import Data.Text.Utf16.Rope.Mixed qualified as Rope From ec6b502d36b92c4d670c3d4b8403097c7cc82896 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jan=20Hr=C4=8Dek?= Date: Sun, 14 Apr 2024 08:35:28 +0200 Subject: [PATCH 2/5] exceptions needed with ghc 9.6+ --- lsp-types/lsp-types.cabal | 3 +++ lsp/src/Language/LSP/Server/Processing.hs | 1 + 2 files changed, 4 insertions(+) diff --git a/lsp-types/lsp-types.cabal b/lsp-types/lsp-types.cabal index 3b6fd89e..267ae671 100644 --- a/lsp-types/lsp-types.cabal +++ b/lsp-types/lsp-types.cabal @@ -90,6 +90,9 @@ library else build-depends: filepath >=1.4 && < 1.6 + if impl(ghc >= 9.6) + build-depends: exceptions ^>=0.10 + ghc-options: -Wall -Wmissing-deriving-strategies -Wno-unticked-promoted-constructors diff --git a/lsp/src/Language/LSP/Server/Processing.hs b/lsp/src/Language/LSP/Server/Processing.hs index ce34d9e3..6329337d 100644 --- a/lsp/src/Language/LSP/Server/Processing.hs +++ b/lsp/src/Language/LSP/Server/Processing.hs @@ -46,6 +46,7 @@ import Data.IxMap import Data.List import Data.List.NonEmpty (NonEmpty (..)) import Data.Map.Strict qualified as Map +import Data.Monoid import Data.String (fromString) import Data.Text qualified as T import Data.Text.Lazy.Encoding qualified as TL From 2390949584e588fde1a7eb7a043d2f2d3a1ac946 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jan=20Hr=C4=8Dek?= Date: Mon, 15 Apr 2024 18:25:28 +0200 Subject: [PATCH 3/5] Small improvements --- lsp-test/src/Language/LSP/Test.hs | 4 ++-- lsp-types/generator/CodeGen.hs | 4 ++-- lsp/src/Language/LSP/Server/Core.hs | 2 +- 3 files changed, 5 insertions(+), 5 deletions(-) diff --git a/lsp-test/src/Language/LSP/Test.hs b/lsp-test/src/Language/LSP/Test.hs index 06e68a77..a2975d54 100644 --- a/lsp-test/src/Language/LSP/Test.hs +++ b/lsp-test/src/Language/LSP/Test.hs @@ -559,7 +559,7 @@ createDoc file languageId contents = do let pred :: SomeRegistration -> [TRegistration Method_WorkspaceDidChangeWatchedFiles] pred (SomeRegistration r@(TRegistration _ SMethod_WorkspaceDidChangeWatchedFiles _)) = [r] pred _ = mempty - regs = concatMap pred $ Map.elems dynCaps + regs = concatMap pred dynCaps watchHits :: FileSystemWatcher -> Bool watchHits (FileSystemWatcher (GlobPattern (InL (Pattern pattern))) kind) = -- If WatchKind is excluded, defaults to all true as per spec @@ -740,7 +740,7 @@ getCodeActionContext doc = do Note that this does not wait for more to come in. -} getCurrentDiagnostics :: TextDocumentIdentifier -> Session [Diagnostic] -getCurrentDiagnostics doc = fromMaybe [] . Map.lookup (toNormalizedUri $ doc ^. L.uri) . curDiagnostics <$> get +getCurrentDiagnostics doc = Map.findWithDefault [] (toNormalizedUri $ doc ^. L.uri) . curDiagnostics <$> get -- | Returns the tokens of all progress sessions that have started but not yet ended. getIncompleteProgressSessions :: Session (Set.Set ProgressToken) diff --git a/lsp-types/generator/CodeGen.hs b/lsp-types/generator/CodeGen.hs index c59433ba..679c5f62 100644 --- a/lsp-types/generator/CodeGen.hs +++ b/lsp-types/generator/CodeGen.hs @@ -367,7 +367,7 @@ printStruct tn s@Structure{name, documentation, since, proposed, deprecated} = d optionalMatcherName <- entityName "Language.LSP.Protocol.Types.Common" ".:!?" let toJsonD = let (unzip -> (args, pairEs)) = flip fmap (zip props [0 ..]) $ \(Property{name, optional}, i) -> - let n :: T.Text = "arg" <> (T.pack $ show i) + let n :: T.Text = "arg" <> T.pack (show i) pairE = case optional of Just True -> dquotes (pretty name) <+> pretty optionalPairerName <+> pretty n _ -> brackets (dquotes (pretty name) <+> "Aeson..=" <+> pretty n) @@ -485,7 +485,7 @@ printEnum tn Enumeration{name, type_, values, supportsCustomValues, documentatio let customCon = let cn = makeConstrName (Just enumName) "Custom" in if custom then Just (cn, pretty cn <+> ty) else Nothing - let cons = normalCons ++ (fmap snd $ maybeToList customCon) + let cons = normalCons ++ (snd <$> maybeToList customCon) ensureImport "Data.Aeson" (QualAs "Aeson") ensureImport "Data.Row.Aeson" (QualAs "Aeson") diff --git a/lsp/src/Language/LSP/Server/Core.hs b/lsp/src/Language/LSP/Server/Core.hs index cd443b42..daa913d9 100644 --- a/lsp/src/Language/LSP/Server/Core.hs +++ b/lsp/src/Language/LSP/Server/Core.hs @@ -496,7 +496,7 @@ getVersionedTextDoc doc = do reverseFileMap :: MonadLsp config m => m (FilePath -> FilePath) reverseFileMap = do vfs <- getsState resVFS - let f fp = fromMaybe fp . Map.lookup fp . reverseMap $ vfs + let f fp = Map.findWithDefault fp fp $ reverseMap vfs return f {-# INLINE reverseFileMap #-} From ad741d4352fb97078bfcd7d6108a7699be674193 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jan=20Hr=C4=8Dek?= Date: Mon, 15 Apr 2024 19:06:27 +0200 Subject: [PATCH 4/5] Add -Wunused-packages, consolidate warning configs, fix few more warnings --- cabal.project | 3 --- lsp-test/bench/SimpleBench.hs | 1 - lsp-test/example/Test.hs | 1 + lsp-test/func-test/FuncTest.hs | 2 -- lsp-test/lsp-test.cabal | 11 +++++++++-- lsp-test/src/Language/LSP/Test.hs | 2 +- lsp-test/src/Language/LSP/Test/Decoding.hs | 2 +- lsp-test/src/Language/LSP/Test/Files.hs | 2 +- lsp-test/src/Language/LSP/Test/Parsing.hs | 2 +- lsp-test/src/Language/LSP/Test/Session.hs | 2 +- lsp-test/test/DummyServer.hs | 2 +- lsp-test/test/Test.hs | 2 +- lsp-types/lsp-types.cabal | 8 +++++++- lsp-types/metamodel/Language/LSP/MetaModel.hs | 1 - .../Language/LSP/Protocol/QuickCheck/Common.hs | 1 - lsp-types/src/Data/IxMap.hs | 2 +- .../src/Language/LSP/Protocol/Message/LspId.hs | 2 +- .../src/Language/LSP/Protocol/Message/Method.hs | 2 +- .../src/Language/LSP/Protocol/Message/Parsing.hs | 2 +- .../Language/LSP/Protocol/Message/Registration.hs | 2 +- .../src/Language/LSP/Protocol/Message/Types.hs | 2 +- lsp-types/test/JsonSpec.hs | 2 +- lsp/example/Reactor.hs | 2 +- lsp/lsp.cabal | 14 +++++++++----- lsp/src/Language/LSP/Server/Core.hs | 2 +- lsp/src/Language/LSP/Server/Processing.hs | 2 +- lsp/src/Language/LSP/VFS.hs | 2 +- 27 files changed, 44 insertions(+), 34 deletions(-) diff --git a/cabal.project b/cabal.project index cf14afb4..f56805ae 100644 --- a/cabal.project +++ b/cabal.project @@ -10,9 +10,6 @@ test-show-details: direct benchmarks: True -package * - ghc-options: -Wunused-packages - package lsp flags: +demo diff --git a/lsp-test/bench/SimpleBench.hs b/lsp-test/bench/SimpleBench.hs index 7b208f3c..ffa89bd5 100644 --- a/lsp-test/bench/SimpleBench.hs +++ b/lsp-test/bench/SimpleBench.hs @@ -1,7 +1,6 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE RankNTypes #-} module Main where diff --git a/lsp-test/example/Test.hs b/lsp-test/example/Test.hs index f6e7f18d..103d9639 100644 --- a/lsp-test/example/Test.hs +++ b/lsp-test/example/Test.hs @@ -6,6 +6,7 @@ import Language.LSP.Protocol.Message import Language.LSP.Protocol.Types import Language.LSP.Test +main :: IO () main = runSession "lsp-demo-reactor-server" fullCaps "test/data/" $ do doc <- openDoc "Rename.hs" "haskell" diff --git a/lsp-test/func-test/FuncTest.hs b/lsp-test/func-test/FuncTest.hs index 1cc2ef9f..2f0102cc 100644 --- a/lsp-test/func-test/FuncTest.hs +++ b/lsp-test/func-test/FuncTest.hs @@ -15,14 +15,12 @@ import Control.Monad.IO.Class import Data.Aeson qualified as J import Data.Maybe import Data.Proxy -import Data.Set qualified as Set import Language.LSP.Protocol.Lens qualified as L import Language.LSP.Protocol.Message import Language.LSP.Protocol.Types import Language.LSP.Server import Language.LSP.Test qualified as Test import System.Exit -import System.IO import System.Process import Test.Hspec import UnliftIO diff --git a/lsp-test/lsp-test.cabal b/lsp-test/lsp-test.cabal index a53c6772..16add6f4 100644 --- a/lsp-test/lsp-test.cabal +++ b/lsp-test/lsp-test.cabal @@ -31,7 +31,11 @@ source-repository head type: git location: https://github.com/haskell/lsp +common warnings + ghc-options: -Wunused-packages + library + import: warnings hs-source-dirs: src default-language: GHC2021 exposed-modules: Language.LSP.Test @@ -89,6 +93,7 @@ library ghc-options: -W test-suite tests + import: warnings type: exitcode-stdio-1.0 hs-source-dirs: test main-is: Test.hs @@ -114,6 +119,7 @@ test-suite tests , unliftio test-suite func-test + import: warnings type: exitcode-stdio-1.0 hs-source-dirs: func-test default-language: GHC2021 @@ -122,7 +128,6 @@ test-suite func-test , base , aeson , co-log-core - , containers , hspec , lens , lsp @@ -132,6 +137,7 @@ test-suite func-test , unliftio test-suite example + import: warnings type: exitcode-stdio-1.0 hs-source-dirs: example default-language: GHC2021 @@ -144,11 +150,12 @@ test-suite example build-tool-depends: lsp:lsp-demo-reactor-server benchmark simple-bench + import: warnings type: exitcode-stdio-1.0 hs-source-dirs: bench default-language: GHC2021 main-is: SimpleBench.hs - ghc-options: -Wall -O2 -eventlog -rtsopts + ghc-options: -Wall -O2 -rtsopts build-depends: , base , extra diff --git a/lsp-test/src/Language/LSP/Test.hs b/lsp-test/src/Language/LSP/Test.hs index a2975d54..df40e356 100644 --- a/lsp-test/src/Language/LSP/Test.hs +++ b/lsp-test/src/Language/LSP/Test.hs @@ -2,7 +2,7 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} {- | Module : Language.LSP.Test diff --git a/lsp-test/src/Language/LSP/Test/Decoding.hs b/lsp-test/src/Language/LSP/Test/Decoding.hs index 76bd842d..594f018d 100644 --- a/lsp-test/src/Language/LSP/Test/Decoding.hs +++ b/lsp-test/src/Language/LSP/Test/Decoding.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module Language.LSP.Test.Decoding where diff --git a/lsp-test/src/Language/LSP/Test/Files.hs b/lsp-test/src/Language/LSP/Test/Files.hs index 06f2842b..1501a0b3 100644 --- a/lsp-test/src/Language/LSP/Test/Files.hs +++ b/lsp-test/src/Language/LSP/Test/Files.hs @@ -1,6 +1,6 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module Language.LSP.Test.Files ( swapFiles, diff --git a/lsp-test/src/Language/LSP/Test/Parsing.hs b/lsp-test/src/Language/LSP/Test/Parsing.hs index 334bb974..0649e755 100644 --- a/lsp-test/src/Language/LSP/Test/Parsing.hs +++ b/lsp-test/src/Language/LSP/Test/Parsing.hs @@ -1,7 +1,7 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module Language.LSP.Test.Parsing ( -- $receiving diff --git a/lsp-test/src/Language/LSP/Test/Session.hs b/lsp-test/src/Language/LSP/Test/Session.hs index 73f9f284..2bf24371 100644 --- a/lsp-test/src/Language/LSP/Test/Session.hs +++ b/lsp-test/src/Language/LSP/Test/Session.hs @@ -5,7 +5,7 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedLabels #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module Language.LSP.Test.Session ( Session(..) diff --git a/lsp-test/test/DummyServer.hs b/lsp-test/test/DummyServer.hs index 1db2a559..e804bacf 100644 --- a/lsp-test/test/DummyServer.hs +++ b/lsp-test/test/DummyServer.hs @@ -1,6 +1,6 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module DummyServer where diff --git a/lsp-test/test/Test.hs b/lsp-test/test/Test.hs index 2f0db501..1a067521 100644 --- a/lsp-test/test/Test.hs +++ b/lsp-test/test/Test.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} import Control.Applicative.Combinators import Control.Concurrent diff --git a/lsp-types/lsp-types.cabal b/lsp-types/lsp-types.cabal index 267ae671..baac145e 100644 --- a/lsp-types/lsp-types.cabal +++ b/lsp-types/lsp-types.cabal @@ -31,7 +31,11 @@ flag force-ospath description: Force a version bound on filepath library, to enable 'OsPath'. +common warnings + ghc-options: -Wunused-packages + library + import: warnings hs-source-dirs: src generated default-language: GHC2021 @@ -53,7 +57,6 @@ library GADTs NegativeLiterals OverloadedStrings - StandaloneKindSignatures StrictData TypeFamilies UndecidableInstances @@ -563,6 +566,7 @@ library Language.LSP.Protocol.Internal.Types.WorkspaceOptions library metamodel + import: warnings -- We don't currently re-export this from the main -- library, but it's here if people want it visibility: public @@ -584,6 +588,7 @@ library metamodel , text >=1 && <2.2 library lsp-types-quickcheck + import: warnings visibility: public hs-source-dirs: quickcheck generated default-language: GHC2021 @@ -630,6 +635,7 @@ executable generator , witherable test-suite lsp-types-test + import: warnings type: exitcode-stdio-1.0 hs-source-dirs: test default-language: GHC2021 diff --git a/lsp-types/metamodel/Language/LSP/MetaModel.hs b/lsp-types/metamodel/Language/LSP/MetaModel.hs index ccc1bfa6..be2127ca 100644 --- a/lsp-types/metamodel/Language/LSP/MetaModel.hs +++ b/lsp-types/metamodel/Language/LSP/MetaModel.hs @@ -5,7 +5,6 @@ module Language.LSP.MetaModel (module Export, metaModel) where import Language.LSP.MetaModel.Types as Export import Data.FileEmbed (makeRelativeToProject) -import Language.Haskell.TH qualified as TH -- | The metamodel used to generate the LSP types in this package. metaModel :: MetaModel diff --git a/lsp-types/quickcheck/Language/LSP/Protocol/QuickCheck/Common.hs b/lsp-types/quickcheck/Language/LSP/Protocol/QuickCheck/Common.hs index 6135a2ce..9f773d97 100644 --- a/lsp-types/quickcheck/Language/LSP/Protocol/QuickCheck/Common.hs +++ b/lsp-types/quickcheck/Language/LSP/Protocol/QuickCheck/Common.hs @@ -5,7 +5,6 @@ module Language.LSP.Protocol.QuickCheck.Common where import Data.Foldable import Data.Row qualified as R import Data.Row.Records qualified as R -import Data.Void import GHC.TypeLits import Language.LSP.Protocol.Message import Language.LSP.Protocol.Types diff --git a/lsp-types/src/Data/IxMap.hs b/lsp-types/src/Data/IxMap.hs index 508ce1dd..b45128e8 100644 --- a/lsp-types/src/Data/IxMap.hs +++ b/lsp-types/src/Data/IxMap.hs @@ -1,5 +1,5 @@ {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE ViewPatterns #-} module Data.IxMap where diff --git a/lsp-types/src/Language/LSP/Protocol/Message/LspId.hs b/lsp-types/src/Language/LSP/Protocol/Message/LspId.hs index 55a3567c..e303cbf3 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/LspId.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/LspId.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module Language.LSP.Protocol.Message.LspId where diff --git a/lsp-types/src/Language/LSP/Protocol/Message/Method.hs b/lsp-types/src/Language/LSP/Protocol/Message/Method.hs index 2fda5db8..3bdee6b0 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/Method.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/Method.hs @@ -2,7 +2,7 @@ {-# LANGUAGE MagicHash #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableSuperClasses #-} {-# OPTIONS_GHC -Wno-orphans #-} diff --git a/lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs b/lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs index 32de1287..b1d00c9e 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs @@ -1,5 +1,5 @@ {-# LANGUAGE LambdaCase #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module Language.LSP.Protocol.Message.Parsing where diff --git a/lsp-types/src/Language/LSP/Protocol/Message/Registration.hs b/lsp-types/src/Language/LSP/Protocol/Message/Registration.hs index 89cf1d19..8495c85d 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/Registration.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/Registration.hs @@ -1,7 +1,7 @@ {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module Language.LSP.Protocol.Message.Registration where diff --git a/lsp-types/src/Language/LSP/Protocol/Message/Types.hs b/lsp-types/src/Language/LSP/Protocol/Message/Types.hs index 320a3b5f..3082a99f 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/Types.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/Types.hs @@ -1,5 +1,5 @@ {-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} module Language.LSP.Protocol.Message.Types where diff --git a/lsp-types/test/JsonSpec.hs b/lsp-types/test/JsonSpec.hs index 9ca69fac..ef41546f 100644 --- a/lsp-types/test/JsonSpec.hs +++ b/lsp-types/test/JsonSpec.hs @@ -2,7 +2,7 @@ {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableInstances #-} -- we're using some deprecated stuff from the LSP spec, that's fine {-# OPTIONS_GHC -fno-warn-deprecations #-} diff --git a/lsp/example/Reactor.hs b/lsp/example/Reactor.hs index 7cf904ed..e001dfea 100644 --- a/lsp/example/Reactor.hs +++ b/lsp/example/Reactor.hs @@ -3,7 +3,7 @@ {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} {- | This is an example language server built with haskell-lsp using a 'Reactor' diff --git a/lsp/lsp.cabal b/lsp/lsp.cabal index 2f5ddf30..206cc269 100644 --- a/lsp/lsp.cabal +++ b/lsp/lsp.cabal @@ -26,10 +26,14 @@ source-repository head type: git location: https://github.com/haskell/lsp +common warnings + ghc-options: -Wall -Wunused-packages -Wno-unticked-promoted-constructors + library + import: warnings hs-source-dirs: src default-language: GHC2021 - ghc-options: -Wall -fprint-explicit-kinds + ghc-options: -fprint-explicit-kinds reexported-modules: , Language.LSP.Protocol.Types , Language.LSP.Protocol.Lens @@ -47,7 +51,6 @@ library Language.LSP.Server.Core Language.LSP.Server.Processing - ghc-options: -Wall build-depends: , aeson >=2 && <2.3 , async ^>=2.2 @@ -78,10 +81,10 @@ library , uuid >=1.3 executable lsp-demo-reactor-server + import: warnings main-is: Reactor.hs hs-source-dirs: example default-language: GHC2021 - ghc-options: -Wall -Wno-unticked-promoted-constructors build-depends: , aeson , base @@ -97,10 +100,10 @@ executable lsp-demo-reactor-server buildable: False executable lsp-demo-simple-server + import: warnings main-is: Simple.hs hs-source-dirs: example default-language: GHC2021 - ghc-options: -Wall -Wno-unticked-promoted-constructors build-depends: , base , lsp @@ -115,6 +118,7 @@ flag demo default: False test-suite lsp-test + import: warnings type: exitcode-stdio-1.0 hs-source-dirs: test main-is: Main.hs @@ -134,5 +138,5 @@ test-suite lsp-test , unordered-containers build-tool-depends: hspec-discover:hspec-discover - ghc-options: -threaded -rtsopts -with-rtsopts=-N -Wall + ghc-options: -threaded -rtsopts -with-rtsopts=-N default-language: GHC2021 diff --git a/lsp/src/Language/LSP/Server/Core.hs b/lsp/src/Language/LSP/Server/Core.hs index daa913d9..c0632ffa 100644 --- a/lsp/src/Language/LSP/Server/Core.hs +++ b/lsp/src/Language/LSP/Server/Core.hs @@ -5,7 +5,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RoleAnnotations #-} {-# LANGUAGE TypeFamilyDependencies #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE CUSKs #-} {-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} diff --git a/lsp/src/Language/LSP/Server/Processing.hs b/lsp/src/Language/LSP/Server/Processing.hs index 6329337d..e8285d4e 100644 --- a/lsp/src/Language/LSP/Server/Processing.hs +++ b/lsp/src/Language/LSP/Server/Processing.hs @@ -2,7 +2,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecursiveDo #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} -- there's just so much! {-# OPTIONS_GHC -Wno-name-shadowing #-} {-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index f354537a..362d3796 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -4,7 +4,7 @@ {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE TypeInType #-} +{-# LANGUAGE DataKinds #-} {-# LANGUAGE ViewPatterns #-} {- | From 2c56e9c0e0b7f04b1216af1a6e7b388a7c161f48 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Jan=20Hr=C4=8Dek?= Date: Tue, 16 Apr 2024 06:21:58 +0200 Subject: [PATCH 5/5] fourmolu --- lsp-test/src/Language/LSP/Test.hs | 2 +- lsp-test/src/Language/LSP/Test/Decoding.hs | 2 +- lsp-test/src/Language/LSP/Test/Files.hs | 2 +- lsp-test/src/Language/LSP/Test/Parsing.hs | 2 +- lsp-test/test/DummyServer.hs | 2 +- lsp-test/test/Test.hs | 2 +- lsp-types/src/Data/IxMap.hs | 2 +- lsp-types/src/Language/LSP/Protocol/Message/Method.hs | 2 +- lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs | 2 +- lsp-types/src/Language/LSP/Protocol/Message/Registration.hs | 2 +- lsp-types/src/Language/LSP/Protocol/Message/Types.hs | 2 +- lsp-types/test/JsonSpec.hs | 2 +- lsp/example/Reactor.hs | 2 +- lsp/src/Language/LSP/Server/Core.hs | 2 +- lsp/src/Language/LSP/Server/Processing.hs | 2 +- lsp/src/Language/LSP/VFS.hs | 2 +- 16 files changed, 16 insertions(+), 16 deletions(-) diff --git a/lsp-test/src/Language/LSP/Test.hs b/lsp-test/src/Language/LSP/Test.hs index df40e356..329cd34c 100644 --- a/lsp-test/src/Language/LSP/Test.hs +++ b/lsp-test/src/Language/LSP/Test.hs @@ -1,8 +1,8 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE DataKinds #-} {- | Module : Language.LSP.Test diff --git a/lsp-test/src/Language/LSP/Test/Decoding.hs b/lsp-test/src/Language/LSP/Test/Decoding.hs index 594f018d..2283a44e 100644 --- a/lsp-test/src/Language/LSP/Test/Decoding.hs +++ b/lsp-test/src/Language/LSP/Test/Decoding.hs @@ -1,6 +1,6 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE DataKinds #-} module Language.LSP.Test.Decoding where diff --git a/lsp-test/src/Language/LSP/Test/Files.hs b/lsp-test/src/Language/LSP/Test/Files.hs index 1501a0b3..4beae3d0 100644 --- a/lsp-test/src/Language/LSP/Test/Files.hs +++ b/lsp-test/src/Language/LSP/Test/Files.hs @@ -1,6 +1,6 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE DataKinds #-} module Language.LSP.Test.Files ( swapFiles, diff --git a/lsp-test/src/Language/LSP/Test/Parsing.hs b/lsp-test/src/Language/LSP/Test/Parsing.hs index 0649e755..9cfe5897 100644 --- a/lsp-test/src/Language/LSP/Test/Parsing.hs +++ b/lsp-test/src/Language/LSP/Test/Parsing.hs @@ -1,7 +1,7 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE DataKinds #-} module Language.LSP.Test.Parsing ( -- $receiving diff --git a/lsp-test/test/DummyServer.hs b/lsp-test/test/DummyServer.hs index e804bacf..3189d2c9 100644 --- a/lsp-test/test/DummyServer.hs +++ b/lsp-test/test/DummyServer.hs @@ -1,6 +1,6 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE DataKinds #-} module DummyServer where diff --git a/lsp-test/test/Test.hs b/lsp-test/test/Test.hs index 1a067521..8e450c23 100644 --- a/lsp-test/test/Test.hs +++ b/lsp-test/test/Test.hs @@ -1,7 +1,7 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE DataKinds #-} import Control.Applicative.Combinators import Control.Concurrent diff --git a/lsp-types/src/Data/IxMap.hs b/lsp-types/src/Data/IxMap.hs index b45128e8..944c89ff 100644 --- a/lsp-types/src/Data/IxMap.hs +++ b/lsp-types/src/Data/IxMap.hs @@ -1,5 +1,5 @@ -{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE DataKinds #-} +{-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} module Data.IxMap where diff --git a/lsp-types/src/Language/LSP/Protocol/Message/Method.hs b/lsp-types/src/Language/LSP/Protocol/Message/Method.hs index 3bdee6b0..10227913 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/Method.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/Method.hs @@ -1,8 +1,8 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableSuperClasses #-} {-# OPTIONS_GHC -Wno-orphans #-} diff --git a/lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs b/lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs index b1d00c9e..e3a636f1 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/Parsing.hs @@ -1,5 +1,5 @@ -{-# LANGUAGE LambdaCase #-} {-# LANGUAGE DataKinds #-} +{-# LANGUAGE LambdaCase #-} module Language.LSP.Protocol.Message.Parsing where diff --git a/lsp-types/src/Language/LSP/Protocol/Message/Registration.hs b/lsp-types/src/Language/LSP/Protocol/Message/Registration.hs index 8495c85d..0b4ad44b 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/Registration.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/Registration.hs @@ -1,7 +1,7 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE DataKinds #-} module Language.LSP.Protocol.Message.Registration where diff --git a/lsp-types/src/Language/LSP/Protocol/Message/Types.hs b/lsp-types/src/Language/LSP/Protocol/Message/Types.hs index 3082a99f..c7fda93f 100644 --- a/lsp-types/src/Language/LSP/Protocol/Message/Types.hs +++ b/lsp-types/src/Language/LSP/Protocol/Message/Types.hs @@ -1,5 +1,5 @@ -{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE DataKinds #-} +{-# LANGUAGE TemplateHaskell #-} module Language.LSP.Protocol.Message.Types where diff --git a/lsp-types/test/JsonSpec.hs b/lsp-types/test/JsonSpec.hs index ef41546f..6d7da36c 100644 --- a/lsp-types/test/JsonSpec.hs +++ b/lsp-types/test/JsonSpec.hs @@ -1,8 +1,8 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeFamilies #-} -{-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableInstances #-} -- we're using some deprecated stuff from the LSP spec, that's fine {-# OPTIONS_GHC -fno-warn-deprecations #-} diff --git a/lsp/example/Reactor.hs b/lsp/example/Reactor.hs index e001dfea..17abc038 100644 --- a/lsp/example/Reactor.hs +++ b/lsp/example/Reactor.hs @@ -1,9 +1,9 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} -{-# LANGUAGE DataKinds #-} {- | This is an example language server built with haskell-lsp using a 'Reactor' diff --git a/lsp/src/Language/LSP/Server/Core.hs b/lsp/src/Language/LSP/Server/Core.hs index c0632ffa..a9a34267 100644 --- a/lsp/src/Language/LSP/Server/Core.hs +++ b/lsp/src/Language/LSP/Server/Core.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE GADTs #-} @@ -5,7 +6,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RoleAnnotations #-} {-# LANGUAGE TypeFamilyDependencies #-} -{-# LANGUAGE DataKinds #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE CUSKs #-} {-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} diff --git a/lsp/src/Language/LSP/Server/Processing.hs b/lsp/src/Language/LSP/Server/Processing.hs index e8285d4e..8ee9ac7c 100644 --- a/lsp/src/Language/LSP/Server/Processing.hs +++ b/lsp/src/Language/LSP/Server/Processing.hs @@ -1,8 +1,8 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecursiveDo #-} -{-# LANGUAGE DataKinds #-} -- there's just so much! {-# OPTIONS_GHC -Wno-name-shadowing #-} {-# OPTIONS_GHC -Wno-unticked-promoted-constructors #-} diff --git a/lsp/src/Language/LSP/VFS.hs b/lsp/src/Language/LSP/VFS.hs index 362d3796..0086f171 100644 --- a/lsp/src/Language/LSP/VFS.hs +++ b/lsp/src/Language/LSP/VFS.hs @@ -1,10 +1,10 @@ +{-# LANGUAGE DataKinds #-} {-# LANGUAGE DuplicateRecordFields #-} {-# LANGUAGE FunctionalDependencies #-} {-# LANGUAGE MultiWayIf #-} {-# LANGUAGE OverloadedLabels #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TemplateHaskell #-} -{-# LANGUAGE DataKinds #-} {-# LANGUAGE ViewPatterns #-} {- |