Skip to content

Commit e473612

Browse files
committed
Investigating the failing formatter tests.
Conclusion is that getDocumentContents is returning junk, doing the idempotent test manually on vscode works as expected, but ends up with junk at the end of the file in the test. 2020-03-12 21:11:05.79062259 [ThreadId 38] - Formatter.doFormatting: contents= "{-# LANGUAGE NoImplicitPrelude #-} module Format where foo :: Int -> Int foo 3 = 2 foo x = x bar :: String -> IO String bar s = do x <- return \"hello\" return \"asdf\" " 2020-03-12 21:11:07.896114974 [ThreadId 7] - <--2--{"result":[{"range":{"start":{"line":0,"character":0},"end":{"line":9,"character":0}},"newText": "{-# LANGUAGE NoImplicitPrelude #-} module Format where foo :: Int -> Int foo 3 = 2 foo x = x bar :: String -> IO String bar s = do x <- return \"hello\" return \"asdf\" "}],"jsonrpc":"2.0","id":1} 2020-03-12 21:11:07.897123428 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/didChange","params":{"textDocument":{"version":0,"uri":"file:///home/alanz/mysrc/github/alanz/haskell-language-server/test/testdata/Format.hs"},"contentChanges":[{"text": "{-# LANGUAGE NoImplicitPrelude #-} module Format where foo :: Int -> Int foo 3 = 2 foo x = x bar :: String -> IO String bar s = do x <- return \"hello\" return \"asdf\" ","range":{"start":{"line":0,"character":0},"end":{"line":9,"character":0}}}]}} ------------------------------------------------------- 2020-03-12 21:11:07.899375044 [ThreadId 213] - Formatter.doFormatting: contents="{-# LANGUAGE NoImplicitPrelude #-} module Format where foo :: Int -> Int foo 3 = 2 foo x = x bar :: String -> IO String bar s = do x <- return \"hello\" return \"asdf\" " 2020-03-12 21:11:07.902320214 [ThreadId 7] - <--2--{"result":[{"range":{"start":{"line":0,"character":0},"end":{"line":9,"character":0}},"newText":"{-# LANGUAGE NoImplicitPrelude #-} module Format where foo :: Int -> Int foo 3 = 2 foo x = x bar :: String -> IO String bar s = do x <- return \"hello\" return \"asdf\" "}],"jsonrpc":"2.0","id":2} 2020-03-12 21:11:07.902812215 [ThreadId 5] - ---> {"jsonrpc":"2.0","method":"textDocument/didChange","params":{"textDocument":{"version":0,"uri":"file:///home/alanz/mysrc/github/alanz/haskell-language-server/test/testdata/Format.hs"},"contentChanges":[{"text": "{-# LANGUAGE NoImplicitPrelude #-} module Format where foo :: Int -> Int foo 3 = 2 foo x = x bar :: String -> IO String bar s = do x <- return \"hello\" return \"asdf\" ","range":{"start":{"line":0,"character":0},"end":{"line":9,"character":0}}}]}} -------------------------------- hieCommand: haskell-language-server --lsp -d -l test-logs/hie-stack-8.6.5.yaml.log HIE cache is warmed up Format formatting provider formatting is idempotent FAILED [1] Failures: test/functional/FormatSpec.hs:64:42: 1) Format, formatting provider, formatting is idempotent expected: "{-# LANGUAGE NoImplicitPrelude #-}\n\nmodule Format where\n\nfoo :: Int -> Int\nfoo 3 = 2\nfoo x = x\n\nbar :: String -> IO String\nbar s = do\n x <- return \"hello\"\n return \"asdf\"\n" but got: "{-# LANGUAGE NoImplicitPrelude #-}\n\nmodule Format where\n\nfoo :: Int -> Int\nfoo 3 = 2\nfoo x = x\n\nbar :: String -> IO String\nbar s = do\n x <- return \"hello\"\n return \"asdf\"\nbar s = do\n x <- return \"hello\"\n return \"asdf\"\n" To rerun use: --match "/Format/formatting provider/formatting is idempotent/" Randomized with seed 1814425400
1 parent a159f38 commit e473612

File tree

5 files changed

+46
-5
lines changed

5 files changed

+46
-5
lines changed

exe/Arguments.hs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,11 @@ data Arguments = Arguments
3232
,argsShakeProfiling :: Maybe FilePath
3333
,argsTesting :: Bool
3434
,argsExamplePlugin :: Bool
35+
-- These next two are for compatibility with existing hie clients, allowing
36+
-- them to just change the name of the exe and still work.
37+
, argsDebugOn :: Bool
38+
, argsLogFile :: Maybe String
39+
3540
}
3641

3742
getArguments :: String -> IO Arguments
@@ -57,6 +62,18 @@ arguments exeName = Arguments
5762
<*> switch (long "example"
5863
<> help "Include the Example Plugin. For Plugin devs only")
5964

65+
<*> switch
66+
( long "debug"
67+
<> short 'd'
68+
<> help "Generate debug output"
69+
)
70+
<*> optional (strOption
71+
( long "logfile"
72+
<> short 'l'
73+
<> metavar "LOGFILE"
74+
<> help "File to log to, defaults to stdout"
75+
))
76+
6077
-- ---------------------------------------------------------------------
6178
-- Set the GHC libdir to the nix libdir if it's present.
6279
getLibdir :: IO FilePath

exe/Main.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -128,8 +128,8 @@ main = do
128128

129129
-- LSP.setupLogger (optLogFile opts) ["hie", "hie-bios"]
130130
-- $ if optDebugOn opts then L.DEBUG else L.INFO
131-
LSP.setupLogger argsShakeProfiling ["hie", "hie-bios"]
132-
$ if argsTesting then L.DEBUG else L.INFO
131+
LSP.setupLogger argsLogFile ["hie", "hie-bios"]
132+
$ if argsDebugOn then L.DEBUG else L.INFO
133133

134134
-- lock to avoid overlapping output on stdout
135135
lock <- newLock

src/Ide/Plugin/Formatter.hs

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -20,12 +20,15 @@ import qualified Data.Map as Map
2020
import qualified Data.Text as T
2121
import Development.IDE.Core.FileStore
2222
import Development.IDE.Core.Rules
23+
import Development.IDE.Core.Shake
2324
-- import Development.IDE.LSP.Server
2425
-- import Development.IDE.Plugin
2526
import Development.IDE.Types.Diagnostics as D
2627
import Development.IDE.Types.Location
2728
-- import Development.Shake hiding ( Diagnostic )
29+
-- import Ide.Logger
2830
import Ide.Types
31+
import Development.IDE.Types.Logger
2932
import Ide.Plugin.Config
3033
import qualified Language.Haskell.LSP.Core as LSP
3134
-- import Language.Haskell.LSP.Messages
@@ -64,7 +67,10 @@ doFormatting lf providers ideState ft uri params = do
6467
Just (toNormalizedFilePath -> fp) -> do
6568
(_, mb_contents) <- runAction ideState $ getFileContents fp
6669
case mb_contents of
67-
Just contents -> provider ideState ft contents fp params
70+
Just contents -> do
71+
logDebug (ideLogger ideState) $ T.pack $
72+
"Formatter.doFormatting: contents=" ++ show contents -- AZ
73+
provider ideState ft contents fp params
6874
Nothing -> return $ Left $ responseError $ T.pack $ "Formatter plugin: could not get file contents for " ++ show uri
6975
Nothing -> return $ Left $ responseError $ T.pack $ "Formatter plugin: uriToFilePath failed for: " ++ show uri
7076
Nothing -> return $ Left $ responseError $ T.pack $ "Formatter plugin: no formatter found for:[" ++ T.unpack mf ++ "]"

test/functional/FormatSpec.hs

Lines changed: 18 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -50,6 +50,20 @@ spec = do
5050
formatRange doc (FormattingOptions 2 True) (Range (Position 2 0) (Position 4 10))
5151
documentContents doc >>= liftIO . (`shouldBe` orig)
5252

53+
-- ---------------------------------
54+
55+
it "formatting is idempotent" $ runSession hieCommand fullCaps "test/testdata" $ do
56+
doc <- openDoc "Format.hs" "haskell"
57+
58+
sendNotification WorkspaceDidChangeConfiguration (DidChangeConfigurationParams (formatLspConfig "ormolu"))
59+
formatDoc doc (FormattingOptions 2 True)
60+
documentContents doc >>= liftIO . (`shouldBe` formattedDocOrmolu)
61+
62+
formatDoc doc (FormattingOptions 2 True)
63+
documentContents doc >>= liftIO . (`shouldBe` formattedDocOrmolu)
64+
65+
-- ---------------------------------
66+
5367
it "can change on the fly" $ runSession hieCommand fullCaps "test/testdata" $ do
5468
doc <- openDoc "Format.hs" "haskell"
5569

@@ -99,6 +113,8 @@ spec = do
99113
-- liftIO $ edits `shouldBe` [TextEdit (Range (Position 1 0) (Position 3 0))
100114
-- "foo x y = do\n print x\n return 42\n"]
101115

116+
-- ---------------------------------
117+
102118
describe "ormolu" $ do
103119
let formatLspConfig provider =
104120
object [ "languageServerHaskell" .= object ["formattingProvider" .= (provider :: Value)] ]
@@ -114,6 +130,8 @@ spec = do
114130
GHC86 -> formatted
115131
_ -> liftIO $ docContent `shouldBe` unchangedOrmolu
116132

133+
-- ---------------------------------------------------------------------
134+
117135
formattedDocOrmolu :: T.Text
118136
formattedDocOrmolu =
119137
"{-# LANGUAGE NoImplicitPrelude #-}\n\n\
@@ -204,7 +222,6 @@ formattedFloskellPostBrittany =
204222
\bar s = do\n\
205223
\ x <- return \"hello\"\n\
206224
\ return \"asdf\"\n\
207-
\ return \"asdf\"\n\
208225
\"
209226

210227
formattedBrittanyPostFloskell :: T.Text

test/utils/TestUtils.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -207,7 +207,8 @@ logFilePath = "hie-" ++ stackYaml ++ ".log"
207207
hieCommand :: String
208208
-- hieCommand = "hie --lsp --bios-verbose -d -l test-logs/" ++ logFilePath
209209
-- hieCommand = "haskell-language-server --lsp"
210-
hieCommand = "haskell-language-server --lsp --test --shake-profiling=test-logs/" ++ logFilePath
210+
-- hieCommand = "haskell-language-server --lsp --test --shake-profiling=test-logs/" ++ logFilePath
211+
hieCommand = "haskell-language-server --lsp -d -l test-logs/" ++ logFilePath
211212

212213
hieCommandVomit :: String
213214
hieCommandVomit = hieCommand ++ " --vomit"

0 commit comments

Comments
 (0)