Merge pull request #1482 from Avi-D-coder/hie-bios

GHC 8.8 support
This commit is contained in:
Alan Zimmerman 2020-01-19 22:56:38 +00:00 committed by GitHub
commit f4600b7951
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
44 changed files with 262 additions and 94 deletions

View File

@ -7,6 +7,8 @@ jobs:
matrix:
stack-def:
YAML_FILE: stack.yaml
stack-8.8.1:
YAML_FILE: stack-8.8.1.yaml
stack-8.6.5:
YAML_FILE: stack-8.6.5.yaml
stack-8.6.4:

View File

@ -7,6 +7,8 @@ jobs:
matrix:
stack-def:
YAML_FILE: stack.yaml
stack-8.8.1:
YAML_FILE: stack-8.8.1.yaml
stack-8.6.5:
YAML_FILE: stack-8.6.5.yaml
stack-8.6.4:

View File

@ -5,8 +5,9 @@ jobs:
vmImage: windows-2019
strategy:
matrix:
stack-def:
YAML_FILE: stack.yaml
# We can't use stack.yaml while it uses ghc-8.8.1
# stack-def:
# YAML_FILE: stack.yaml
stack-8.6.5:
YAML_FILE: stack-8.6.5.yaml
stack-8.6.4:

View File

@ -149,7 +149,7 @@ jobs:
cabal:
working_directory: ~/build
docker:
- image: quay.io/haskell_works/ghc-8.6.5
- image: haskell:8.8.1
steps:
- checkout
- run:
@ -161,18 +161,15 @@ jobs:
- restore-cache:
keys:
- cabal-{{ .Environment.HIE_CACHE }}-{{ arch }}-{{ .Environment.CIRCLE_JOB }}
- run:
name: Cabal version
command: cabal --version
- run:
name: Update
command: cabal new-update
command: cabal update
- run:
name: Configure
command: cabal new-configure --enable-tests
command: cabal configure --enable-tests
- run:
name: Build
command: cabal new-build -j1 # need j1, else ghc-lib-parser triggers OOM
command: cabal build -j1 # need j1, else ghc-lib-parser triggers OOM
no_output_timeout: 30m
- save_cache:
key: cabal-{{ .Environment.HIE_CACHE }}-{{ arch }}-{{ .Environment.CIRCLE_JOB }}

View File

@ -1,10 +1,13 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
module Main where
import qualified Control.Exception as E
import Control.Monad
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#endif
import Data.Version (showVersion)
import qualified Data.Text as T
import qualified Data.Text.IO as T

View File

@ -23,7 +23,6 @@ import Control.Monad ( when )
import Data.IORef
import qualified Data.Map.Strict as Map
-- import qualified Data.IntMap.Strict as IM
import Data.Semigroup ((<>), Semigroup)
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Data.Aeson
@ -37,7 +36,12 @@ import Haskell.Ide.Engine.PluginUtils
import DynFlags
import GHC
import qualified HscTypes
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup ((<>), Semigroup)
import Outputable (renderWithStyle)
#endif
import Language.Haskell.LSP.Types ( NormalizedUri(..), toNormalizedUri )
import Haskell.Ide.Engine.GhcUtils

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveAnyClass #-}
@ -111,13 +112,17 @@ import qualified Data.List as List
import Data.Dynamic ( Dynamic )
import qualified Data.Map as Map
import Data.Maybe
import Data.Monoid ( (<>) )
import qualified Data.Set as S
import Data.String
import qualified Data.Text as T
import Data.Typeable ( TypeRep
, Typeable
)
import Data.Typeable ( TypeRep )
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ( (<>) )
import Data.Typeable ( Typeable )
#endif
import System.Directory
import GhcMonad
import GHC.Generics

View File

@ -104,8 +104,8 @@ getHieVersions = do
& mapMaybe
(T.stripPrefix stackYamlPrefix >=> T.stripSuffix stackYamlSuffix)
& map T.unpack
-- the following line excludes `8.6.3` on windows systems
& filter (\p -> not isWindowsSystem || p /= "8.6.3")
-- the following line excludes `8.6.3` and `8.8.1` on windows systems
& filter (\p -> not (isWindowsSystem && p `elem` ["8.6.3","8.8.1"]))
& sort
return hieVersions

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
@ -23,7 +24,9 @@ import qualified Data.List as List
import qualified Data.Text as T
import qualified Data.Map as Map
import Data.Maybe
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup (Semigroup(..))
#endif
import Data.Typeable
import GHC.Generics ( Generic )

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
@ -19,7 +20,11 @@ import Control.Monad.IO.Class
import Control.Monad.Trans.Except
import Data.Aeson hiding (Error)
import Data.Maybe
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#endif
import qualified Data.Text as T
import GHC.Generics
import Haskell.Ide.Engine.MonadFunctions

View File

@ -15,7 +15,8 @@ import Haskell.Ide.Engine.PluginUtils
import Language.Haskell.Brittany
import qualified Language.Haskell.LSP.Types as J
import qualified Language.Haskell.LSP.Types.Lens as J
import System.FilePath (FilePath, takeDirectory)
import System.FilePath
import Data.Maybe (maybeToList)
brittanyDescriptor :: PluginId -> PluginDescriptor

View File

@ -14,7 +14,9 @@ import Data.Function
import qualified Data.HashMap.Strict as HM
import Data.List
import Data.Maybe
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#endif
import qualified Data.Text as T
import Name
import GHC.Generics

View File

@ -26,7 +26,9 @@ module Haskell.Ide.Engine.Plugin.GhcMod
) where
import Data.Aeson
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#endif
import GHC.Generics
import qualified Haskell.Ide.Engine.Ghc as HIE
import Haskell.Ide.Engine.MonadTypes

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
@ -107,7 +108,11 @@ getDocsForName df name = do
case mf of
Nothing -> return Nothing
Just f -> do
#if __GLASGOW_HASKELL__ >= 808
ehi <- readInterfaceFile nameCacheFromIdeM f True
#else
ehi <- readInterfaceFile nameCacheFromIdeM f
#endif
case ehi of
Left message -> do
debugm $ "Haddock docs couldn't be loaded as readInterfaceFile failed with: " ++ message
@ -152,8 +157,15 @@ prettyprintType n t = T.unlines
, "```\n"
]
unwrap :: Foldable w => w a -> a
unwrap = foldl1 (const id)
renderDocs :: MDoc Name -> T.Text
#if __GLASGOW_HASKELL__ >= 808
renderDocs = markup renderMarkDown . _doc . fmap unwrap
#else
renderDocs = markup renderMarkDown . _doc
#endif
renderMarkDown :: DocMarkup Name T.Text
renderMarkDown =
@ -162,7 +174,11 @@ renderMarkDown =
, markupParagraph = (<> "\n\n")
, markupAppend = mappend
, markupIdentifier = surround "`" . T.pack . getOccString
#if __GLASGOW_HASKELL__ >= 808
, markupIdentifierUnchecked = T.pack . occNameString . snd . unwrap
#else
, markupIdentifierUnchecked = T.pack . occNameString . snd
#endif
, markupModule = surround "**" . T.pack
, markupWarning = surround "*"
, markupEmphasis = surround "*"
@ -174,9 +190,16 @@ renderMarkDown =
, markupDefList = T.unlines . map (\(a, b) -> a <> " :: " <> b)
, markupCodeBlock = \x -> "\n```haskell\n" <> removeInner x <> "\n```\n"
, markupHyperlink = \h ->
T.pack $ maybe
#if __GLASGOW_HASKELL__ >= 808
let url = T.pack $ hyperlinkUrl h
in maybe
url
(\l -> "["<>l<>"]("<>url<>")")
#else
T.pack $ maybe
(hyperlinkUrl h)
(\l -> "["<>l<>"]("<>hyperlinkUrl h<>")")
#endif
(hyperlinkLabel h)
, markupAName = T.pack
, markupPic = const ""

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveAnyClass #-}
@ -13,7 +14,9 @@ import Control.Monad
import Data.Aeson
import Data.Foldable
import Data.Maybe
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ( (<>) )
#endif
import qualified Data.Text as T
import qualified Data.Text.IO as T
import qualified GHC.Generics as Generics

View File

@ -25,7 +25,11 @@ import qualified Data.HashMap.Strict as HM
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import Data.Maybe
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#else
import qualified Data.Set as S
#endif
#if MIN_VERSION_Cabal(2,2,0)
import Distribution.PackageDescription.Parsec
import Distribution.Types.VersionRange
@ -297,7 +301,11 @@ editCabalPackage file modulePath pkgName fileMap = do
-- Add it to the bottom of the dependencies list
-- TODO: we could sort the depencies and then insert it,
-- or insert it in order iff the list is already sorted.
#if __GLASGOW_HASKELL__ >= 808
newDeps = oldDeps ++ [Dependency (mkPackageName (T.unpack dep)) anyVersion S.empty]
#else
newDeps = oldDeps ++ [Dependency (mkPackageName (T.unpack dep)) anyVersion]
#endif
-- | Provide a code action to add a package to the local package.yaml or cabal file.
-- Reads from diagnostics the unknown import module path and searches for it on Hoogle.

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
@ -8,7 +9,9 @@ module Haskell.Ide.Engine.Plugin.Pragmas where
import Control.Lens
import Data.Aeson
import qualified Data.HashMap.Strict as H
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#endif
import qualified Data.Text as T
import qualified GHC.Generics as Generics
import Haskell.Ide.Engine.MonadTypes hiding (_range)

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ExistentialQuantification #-}
@ -25,9 +26,11 @@ where
import Control.Concurrent.Async
import GHC.Conc
import qualified Control.Concurrent.STM as STM
import Control.Monad.IO.Class ( liftIO
, MonadIO
)
import Control.Monad.IO.Class ( MonadIO )
#if __GLASGOW_HASKELL__ < 808
import Control.Monad.IO.Class ( liftIO )
#endif
import Control.Monad.Reader.Class ( ask
, MonadReader
)

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}
@ -32,7 +33,10 @@ import Data.Default
import Data.Foldable
import qualified Data.Map as Map
import Data.Maybe
import Data.Semigroup (Semigroup(..), Option(..), option)
import Data.Semigroup (Option(..), option)
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup (Semigroup(..), )
#endif
import qualified Data.Set as S
import qualified Data.SortedList as SL
import qualified Data.Text as T

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
@ -25,7 +26,11 @@ module Haskell.Ide.Engine.Support.HieExtras
, getFormattingPlugin
) where
#if __GLASGOW_HASKELL__ < 808
import Data.Semigroup (Semigroup(..))
import Var
#endif
import ConLike
import Control.Monad.Reader
import Control.Monad.Except
@ -62,7 +67,6 @@ import Packages
import SrcLoc
import TcEnv
import Type
import Var
import Module hiding (getModule)
-- ---------------------------------------------------------------------
@ -336,7 +340,11 @@ gotoModule rfm mn = do
flushFinderCaches env
findImportedModule env mn Nothing
case fr of
#if __GLASGOW_HASKELL__ < 808
Found (ModLocation (Just src) _ _) _ -> do
#else
Found (ModLocation (Just src) _ _ _) _ -> do
#endif
fp <- reverseMapFile rfm src
let r = Range (Position 0 0) (Position 0 0)

View File

@ -1,6 +1,5 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Information and display strings for HIE's version
-- and the current project's version

View File

@ -52,7 +52,6 @@ extra-deps:
- wai-3.2.2.1 # for network and network-bsd
flags:
haskell-ide-engine:
pedantic: true

View File

@ -40,7 +40,6 @@ extra-deps:
- unix-time-0.4.7
flags:
haskell-ide-engine:
pedantic: true

38
stack-8.8.1.yaml Normal file
View File

@ -0,0 +1,38 @@
resolver: nightly-2020-01-17
packages:
- .
- hie-plugin-api
extra-deps:
# - ./submodules/HaRe
- apply-refact-0.7.0.0
- bytestring-trie-0.2.5.0
- cabal-helper-1.0.0.0
- clock-0.7.2
- constrained-dynamic-0.1.0.0
- floskell-0.10.2
- haddock-api-2.23.0
- haddock-library-1.8.0
- hie-bios-0.3.2
- hoogle-5.0.17.11
- hsimport-0.11.0
- semigroups-0.18.5
- temporary-1.2.1.1
- haskell-src-exts-1.21.1
- ilist-0.3.1.0
- monad-dijkstra-0.1.1.2
flags:
haskell-ide-engine:
pedantic: true
hie-plugin-api:
pedantic: true
# allow-newer: true
nix:
packages: [ icu libcxx zlib ]
concurrent-tests: false

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
module FunctionalCodeActionsSpec where
@ -11,7 +12,9 @@ import Data.Default
import qualified Data.HashMap.Strict as HM
import qualified Data.Set as Set
import Data.Maybe
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#endif
import qualified Data.Text as T
import Haskell.Ide.Engine.Config
import Language.Haskell.LSP.Test as Test
@ -289,7 +292,9 @@ spec = describe "code actions" $ do
executeCodeAction action
contents <- getDocumentEdit . TextDocumentIdentifier =<< getDocUri "add-package-test.cabal"
liftIO $ T.lines contents `shouldSatisfy` \x -> any (\l -> "text -any" `T.isSuffixOf` (x !! l)) [15, 16]
liftIO $
T.lines contents `shouldSatisfy` \x ->
any (\l -> "text -any" `T.isSuffixOf` l || "text : {} -any" `T.isSuffixOf` l) x
it "adds to hpack package.yaml files" $
runSession hieCommand fullCaps "test/testdata/addPackageTest/hpack-exe" $ do
@ -384,6 +389,14 @@ spec = describe "code actions" $ do
suggestion <-
case ghcVersion of
GHC88 -> do
liftIO $ map (^. L.title) cas `shouldMatchList`
[ "Substitute hole (Int) with x ([Int])"
, "Substitute hole (Int) with foo ([Int] -> Int Valid hole fits include)"
, "Substitute hole (Int) with maxBound (forall a. Bounded a => a with maxBound @Int)"
, "Substitute hole (Int) with minBound (forall a. Bounded a => a with minBound @Int)"
]
return "x"
GHC86 -> do
liftIO $ map (^. L.title) cas `shouldMatchList`
[ "Substitute hole (Int) with x ([Int])"
@ -399,12 +412,6 @@ spec = describe "code actions" $ do
, "Substitute hole (Int) with undefined (forall (a :: TYPE r). GHC.Stack.Types.HasCallStack => a)"
]
return "maxBound"
GHCPre84 -> do
liftIO $ map (^. L.title) cas `shouldMatchList`
[ "Substitute hole (Int) with x ([Int])"
, "Substitute hole (Int) with foo ([Int] -> Int)"
]
return "x"
executeCodeAction $ head cas
@ -424,6 +431,13 @@ spec = describe "code actions" $ do
suggestion <-
case ghcVersion of
GHC88 -> do
liftIO $ map (^. L.title) cas `shouldMatchList`
[ "Substitute hole (A) with stuff (A -> A)"
, "Substitute hole (A) with x ([A])"
, "Substitute hole (A) with foo2 ([A] -> A)"
]
return "stuff"
GHC86 -> do
liftIO $ map (^. L.title) cas `shouldMatchList`
[ "Substitute hole (A) with stuff (A -> A)"
@ -439,13 +453,6 @@ spec = describe "code actions" $ do
, "Substitute hole (A) with foo2 ([A] -> A)"
]
return "undefined"
GHCPre84 -> do
liftIO $ map (^. L.title) cas `shouldMatchList`
[ "Substitute hole (A) with stuff (A -> A)"
, "Substitute hole (A) with x ([A])"
, "Substitute hole (A) with foo2 ([A] -> A)"
]
return "stuff"
executeCodeAction $ head cas

View File

@ -1 +0,0 @@
resolver: ghc-8.2.1

View File

@ -0,0 +1 @@
resolver: ghc-8.8.1

View File

@ -1 +0,0 @@
resolver: lts-11.14

View File

@ -0,0 +1 @@
resolver: lts-14.18

View File

@ -153,7 +153,7 @@ applyRefactSpec = do
let filePath = filePathToUri fp
let req = applyAllCmd filePath
isExpectedError (IdeResultFail (IdeError PluginError err _)) =
"Illegal symbol '.' in type" `T.isInfixOf` err
"Illegal symbol " `T.isInfixOf` err
isExpectedError _ = False
r <- withCurrentDirectory "./test/testdata" $ runIGM testPlugins fp req
r `shouldSatisfy` isExpectedError

View File

@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-}
module LiquidSpec where
@ -7,7 +8,9 @@ import Data.List
import qualified Data.ByteString.Lazy as BS
import qualified Data.Text as T
import qualified Data.Text.IO as T
#if __GLASGOW_HASKELL__ < 808
import Data.Monoid ((<>))
#endif
import Haskell.Ide.Engine.MonadTypes
import Haskell.Ide.Engine.Plugin.Liquid
import System.Directory

View File

@ -63,27 +63,48 @@ packageSpec = do
uri = filePathToUri $ fp </> "add-package-test.cabal"
args = AddParams fp (fp </> "AddPackage.hs") "text"
act = addCmd args
textEdits =
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "cabal-version: >=1.10\n"
, "name: add-package-test\n"
, "version: 0.1.0.0\n"
, "license: BSD3\n"
, "maintainer: luke_lau@icloud.com\n"
, "author: Luke Lau\n"
, "build-type: Simple\n"
, "extra-source-files:\n"
, " ChangeLog.md"
textEdits = case ghcVersion of
GHC88 ->
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "cabal-version: >=1.10\n"
, "name: add-package-test\n"
, "version: 0.1.0.0\n"
, "license: BSD3\n"
, "maintainer: luke_lau@icloud.com\n"
, "author: Luke Lau\n"
, "build-type: Simple\n"
, "extra-source-files: ChangeLog.md"
]
, TextEdit (Range (Position 10 0) (Position 13 34)) $ T.concat
[ " main-is: AddPackage.hs\n"
, " default-language: Haskell2010\n"
, " build-depends:\n"
, " base >=4.7 && <5,\n"
, " text : {} -any"
]
]
, TextEdit (Range (Position 10 0) (Position 13 34)) $ T.concat
[ " main-is: AddPackage.hs\n"
, " default-language: Haskell2010\n"
, " build-depends:\n"
, " base >=4.7 && <5,\n"
, " text -any"
_ ->
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "cabal-version: >=1.10\n"
, "name: add-package-test\n"
, "version: 0.1.0.0\n"
, "license: BSD3\n"
, "maintainer: luke_lau@icloud.com\n"
, "author: Luke Lau\n"
, "build-type: Simple\n"
, "extra-source-files:\n"
, " ChangeLog.md"
]
, TextEdit (Range (Position 10 0) (Position 13 34)) $ T.concat
[ " main-is: AddPackage.hs\n"
, " default-language: Haskell2010\n"
, " build-depends:\n"
, " base >=4.7 && <5,\n"
, " text -any"
]
]
]
res = IdeResultOk
$ WorkspaceEdit (Just $ H.singleton uri textEdits) Nothing
testCommand testPlugins fp act "package" "add" args res
@ -96,28 +117,49 @@ packageSpec = do
uri = filePathToUri $ fp </> "add-package-test.cabal"
args = AddParams fp (fp </> "AddPackage.hs") "text"
act = addCmd args
textEdits =
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "cabal-version: >=1.10\n"
, "name: add-package-test\n"
, "version: 0.1.0.0\n"
, "license: BSD3\n"
, "maintainer: luke_lau@icloud.com\n"
, "author: Luke Lau\n"
, "build-type: Simple\n"
, "extra-source-files:\n"
, " ChangeLog.md"
textEdits = case ghcVersion of
GHC88 ->
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "cabal-version: >=1.10\n"
, "name: add-package-test\n"
, "version: 0.1.0.0\n"
, "license: BSD3\n"
, "maintainer: luke_lau@icloud.com\n"
, "author: Luke Lau\n"
, "build-type: Simple\n"
, "extra-source-files: ChangeLog.md"
]
, TextEdit (Range (Position 10 0) (Position 13 34)) $ T.concat
[ " exposed-modules: AddPackage\n"
, " default-language: Haskell2010\n"
, " build-depends:\n"
, " base >=4.7 && <5,\n"
, " text : {} -any"
]
]
, TextEdit (Range (Position 10 0) (Position 13 34)) $ T.concat
[ " exposed-modules:\n"
, " AddPackage\n"
, " default-language: Haskell2010\n"
, " build-depends:\n"
, " base >=4.7 && <5,\n"
, " text -any"
_ ->
List
[ TextEdit (Range (Position 0 0) (Position 7 27)) $ T.concat
[ "cabal-version: >=1.10\n"
, "name: add-package-test\n"
, "version: 0.1.0.0\n"
, "license: BSD3\n"
, "maintainer: luke_lau@icloud.com\n"
, "author: Luke Lau\n"
, "build-type: Simple\n"
, "extra-source-files:\n"
, " ChangeLog.md"
]
, TextEdit (Range (Position 10 0) (Position 13 34)) $ T.concat
[ " exposed-modules:\n"
, " AddPackage\n"
, " default-language: Haskell2010\n"
, " build-depends:\n"
, " base >=4.7 && <5,\n"
, " text -any"
]
]
]
res = IdeResultOk
$ WorkspaceEdit (Just $ H.singleton uri textEdits) Nothing
testCommand testPlugins fp act "package" "add" args res

View File

@ -143,23 +143,25 @@ files =
]
data GhcVersion
= GHC86
= GHC88
| GHC86
| GHC84
| GHCPre84
deriving (Eq,Show)
ghcVersion :: GhcVersion
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,6,0,0)))
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,8,0,0)))
ghcVersion = GHC88
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,6,0,0)))
ghcVersion = GHC86
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)))
ghcVersion = GHC84
#else
ghcVersion = GHCPre84
#endif
stackYaml :: FilePath
stackYaml =
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,6,5,0)))
#if (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,8,1,0)))
"stack-8.8.1.yaml"
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,6,5,0)))
"stack-8.6.5.yaml"
#elif (defined(MIN_VERSION_GLASGOW_HASKELL) && (MIN_VERSION_GLASGOW_HASKELL(8,6,4,0)))
"stack-8.6.4.yaml"

View File

@ -11,16 +11,16 @@ import System.Process
main :: IO ()
main = hspec $
describe "version checking" $ do
it "picks up a stack.yaml with 8.2.1" $
withCurrentDirectory "test/testdata/wrapper/8.2.1" $ do
it "picks up a stack.yaml with 8.8.1" $
withCurrentDirectory "test/testdata/wrapper/8.8.1" $ do
d <- getCurrentDirectory
cradle <- liftIO (findLocalCradle (d </> "File.hs"))
getProjectGhcVersion cradle `shouldReturn` "8.2.1"
it "picks up a stack.yaml with 8.2.2" $
withCurrentDirectory "test/testdata/wrapper/lts-11.14" $ do
getProjectGhcVersion cradle `shouldReturn` "8.8.1"
it "picks up a stack.yaml with 8.6.5" $
withCurrentDirectory "test/testdata/wrapper/lts-14.18" $ do
d <- getCurrentDirectory
cradle <- liftIO (findLocalCradle (d </> "File.hs"))
getProjectGhcVersion cradle `shouldReturn` "8.2.2"
getProjectGhcVersion cradle `shouldReturn` "8.6.5"
it "picks up whatever version of ghc is on this machine" $
withCurrentDirectory "test/testdata/wrapper/ghc" $ do
d <- getCurrentDirectory