Drop CPP directives for GHC 8.2.2 in test folder

This commit is contained in:
fendor 2019-10-30 18:27:02 +01:00 committed by fendor
parent 2d39a8d2a4
commit 7cf1295a28
5 changed files with 2 additions and 86 deletions

View File

@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE CPP #-}
module FunctionalCodeActionsSpec where
@ -213,8 +212,6 @@ spec = describe "code actions" $ do
]
]
describe "add package suggestions" $ do
-- Only execute this test with ghc 8.4.4, below seems to be broken in the package.
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)))
it "adds to .cabal files" $ runSession hieCommand fullCaps "test/testdata/addPackageTest/cabal-exe" $ do
doc <- openDoc "AddPackage.hs" "haskell"
@ -240,7 +237,7 @@ spec = describe "code actions" $ do
contents <- getDocumentEdit . TextDocumentIdentifier =<< getDocUri "add-package-test.cabal"
liftIO $ T.lines contents `shouldSatisfy` \x -> any (\l -> "text -any" `T.isSuffixOf` (x !! l)) [15, 16]
#endif
it "adds to hpack package.yaml files" $
runSession hieCommand fullCaps "test/testdata/addPackageTest/hpack-exe" $ do
doc <- openDoc "app/Asdf.hs" "haskell"

View File

@ -100,7 +100,6 @@ applyRefactSpec = do
PublishDiagnosticsParams
{ _uri = filePath
, _diagnostics = List
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)))
[Diagnostic {_range = Range { _start = Position {_line = 12, _character = 23}
, _end = Position {_line = 12, _character = 100000}}
, _severity = Just DsInfo
@ -108,23 +107,6 @@ applyRefactSpec = do
, _source = Just "hlint"
, _message = T.pack filePathNoUri <> ":13:24: error:\n Operator applied to too few arguments: +\n data instance Sing (z :: (a :~: b)) where\n> SRefl :: Sing Refl +\n\n"
, _relatedInformation = Nothing }]}
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)))
[Diagnostic {_range = Range { _start = Position {_line = 13, _character = 0}
, _end = Position {_line = 13, _character = 100000}}
, _severity = Just DsInfo
, _code = Just (StringValue "parser")
, _source = Just "hlint"
, _message = "Parse error: virtual }\n data instance Sing (z :: (a :~: b)) where\n SRefl :: Sing Refl +\n> \n\n"
, _relatedInformation = Nothing }]}
#else
[Diagnostic {_range = Range { _start = Position {_line = 11, _character = 28}
, _end = Position {_line = 11, _character = 100000}}
, _severity = Just DsInfo
, _code = Just "parser"
, _source = Just "hlint"
, _message = "Parse error: :~:\n import Data.Type.Equality ((:~:) (..), (:~~:) (..))\n \n> data instance Sing (z :: (a :~: b)) where\n SRefl :: Sing Refl +\n\n"
, _relatedInformation = Nothing }]}
#endif
testCommand testPlugins act "applyrefact" "lint" arg res
-- ---------------------------------

View File

@ -5,9 +5,6 @@ module GhcModPluginSpec where
import Control.Exception
import qualified Data.HashMap.Strict as H
import qualified Data.Map as Map
#if __GLASGOW_HASKELL__ < 804
-- import Data.Monoid
#endif
import qualified Data.Set as S
import qualified Data.Text as T
import Haskell.Ide.Engine.Ghc
@ -486,11 +483,6 @@ ghcmodSpec =
, (Range (toPos (33, 15)) (toPos (33, 19)), "Int -> Test -> ShowS")
, (Range (toPos (33, 15)) (toPos (33, 19)), "Test -> String")
, (Range (toPos (33, 15)) (toPos (33, 19)), "[Test] -> ShowS")
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)))
#else
, (Range (toPos (33, 15)) (toPos (33, 19)), "Int -> Test -> ShowS")
, (Range (toPos (33, 15)) (toPos (33, 19)), "[Test] -> ShowS")
#endif
]
testCommand testPlugins act "ghcmod" "type" arg res
@ -505,11 +497,6 @@ ghcmodSpec =
[ (Range (toPos (33, 21)) (toPos (33, 23)), "(Test -> Test -> Bool) -> (Test -> Test -> Bool) -> Eq Test")
, (Range (toPos (33, 21)) (toPos (33, 23)), "Test -> Test -> Bool")
, (Range (toPos (33, 21)) (toPos (33, 23)), "Test -> Test -> Bool")
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)))
#else
, (Range (toPos (33, 21)) (toPos (33, 23)), "Test -> Test -> Bool")
, (Range (toPos (33, 21)) (toPos (33, 23)), "Test -> Test -> Bool")
#endif
]
testCommand testPlugins act "ghcmod" "type" arg res

View File

@ -64,7 +64,6 @@ packageSpec = do
args = AddParams fp (fp </> "AddPackage.hs") "text"
act = addCmd' args
textEdits =
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)))
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "cabal-version: >=1.10\n"
@ -85,25 +84,6 @@ packageSpec = do
, " text -any"
]
]
#else
List -- TODO: this seems to indicate that the command does nothing
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "name: add-package-test\n"
, "version: 0.1.0.0\n"
, "cabal-version: >=1.10\n"
, "build-type: Simple\n"
, "license: BSD3\n"
, "maintainer: luke_lau@icloud.com\n"
, "author: Luke Lau\n"
, "extra-source-files:\n"
, " ChangeLog.md"
]
, TextEdit (Range (Position 9 0) (Position 13 34)) $ T.concat
[ "executable AddPackage\n"
, " main-is: AddPackage.hs\n"
]
]
#endif
res = IdeResultOk
$ WorkspaceEdit (Just $ H.singleton uri textEdits) Nothing
testCommand testPlugins act "package" "add" args res
@ -117,7 +97,6 @@ packageSpec = do
args = AddParams fp (fp </> "AddPackage.hs") "text"
act = addCmd' args
textEdits =
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)))
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "cabal-version: >=1.10\n"
@ -139,29 +118,6 @@ packageSpec = do
, " text -any"
]
]
#else
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "name: add-package-test\n"
, "version: 0.1.0.0\n"
, "cabal-version: >=1.10\n"
, "build-type: Simple\n"
, "license: BSD3\n"
, "maintainer: luke_lau@icloud.com\n"
, "author: Luke Lau\n"
, "extra-source-files:\n"
, " ChangeLog.md"
]
, TextEdit (Range (Position 10 0) (Position 13 34)) $ T.concat
[ " exposed-modules:\n"
, " AddPackage\n"
, " build-depends:\n"
, " base >=4.7 && <5,\n"
, " text -any\n"
, " default-language: Haskell2010\n"
]
]
#endif
res = IdeResultOk
$ WorkspaceEdit (Just $ H.singleton uri textEdits) Nothing
testCommand testPlugins act "package" "add" args res
@ -239,7 +195,7 @@ packageSpec = do
]
]
testCommand testPlugins act "package" "add" args res
it "Do nothing on NoPackage"
$ withCurrentDirectory (testdata </> "invalid")
$ do

View File

@ -151,12 +151,6 @@ stackYaml =
"stack-8.4.3.yaml"
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,2,0)))
"stack-8.4.2.yaml"
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,2,2,0)))
"stack-8.2.2.yaml"
#elif __GLASGOW_HASKELL__ >= 802
"stack-8.2.1.yaml"
#else
"stack-8.0.2.yaml"
#endif
logFilePath :: String