Skip to content

Commit

Permalink
refactor: Create a type-level expect failure
Browse files Browse the repository at this point in the history
  • Loading branch information
sgillespie committed Sep 24, 2024
1 parent edfc677 commit 50d4b0a
Show file tree
Hide file tree
Showing 3 changed files with 47 additions and 10 deletions.
42 changes: 33 additions & 9 deletions ghcide/test/exe/ReferenceTests.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}

Expand Down Expand Up @@ -30,10 +31,13 @@ import Ide.PluginUtils (toAbsolute)
import Ide.Types
import System.FilePath (addTrailingPathSeparator,
(</>))
import Test.Hls (FromServerMessage' (..),
import Test.Hls (BrokenBehavior (..),
ExpectBroken (..),
FromServerMessage' (..),
SMethod (..),
TCustomMessage (..),
TNotificationMessage (..))
TNotificationMessage (..),
unCurrent)
import Test.Hls.FileSystem (copyDir)
import Test.Tasty
import Test.Tasty.HUnit
Expand Down Expand Up @@ -90,15 +94,24 @@ tests = testGroup "references"
]

-- TODO: references provider does not respect includeDeclaration parameter
, referenceTest "INCORRECTLY returns declarations when we ask to exclude them"
, referenceTestExpectFail "works when we ask to exclude declarations"
("References.hs", 4, 7)
NoExcludeDeclaration
[ ("References.hs", 4, 6)
, ("References.hs", 6, 0)
, ("References.hs", 6, 14)
, ("References.hs", 9, 7)
, ("References.hs", 10, 11)
]
(BrokenIdeal
[ ("References.hs", 6, 0)
, ("References.hs", 6, 14)
, ("References.hs", 9, 7)
, ("References.hs", 10, 11)
]
)
(BrokenCurrent
[ ("References.hs", 4, 6)
, ("References.hs", 6, 0)
, ("References.hs", 6, 14)
, ("References.hs", 9, 7)
, ("References.hs", 10, 11)
]
)
]

, testGroup "can get references to non FOIs"
Expand Down Expand Up @@ -194,6 +207,17 @@ referenceTest name loc includeDeclaration expected =
where
docs = map fst3 expected

referenceTestExpectFail
:: (HasCallStack)
=> String
-> SymbolLocation
-> IncludeDeclaration
-> ExpectBroken 'Ideal [SymbolLocation]
-> ExpectBroken 'Current [SymbolLocation]
-> TestTree
referenceTestExpectFail name loc includeDeclaration _ =
referenceTest name loc includeDeclaration . unCurrent

type SymbolLocation = (FilePath, UInt, UInt)

expectSameLocations :: (HasCallStack) => FilePath -> [Location] -> [SymbolLocation] -> Assertion
Expand Down
14 changes: 13 additions & 1 deletion hls-test-utils/src/Test/Hls.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,10 @@ module Test.Hls
-- * Helpful re-exports
PluginDescriptor,
IdeState,
-- * Helpers for expected test case failuers
BrokenBehavior(..),
ExpectBroken(..),
unCurrent,
-- * Assertion helper functions
waitForProgressDone,
waitForAllProgressDone,
Expand Down Expand Up @@ -166,6 +170,15 @@ instance Pretty LogTestHarness where
LogCleanup -> "Cleaned up temporary directory"
LogNoCleanup -> "No cleanup of temporary directory"

data BrokenBehavior = Current | Ideal

data ExpectBroken (k :: BrokenBehavior) a where
BrokenCurrent :: a -> ExpectBroken 'Current a
BrokenIdeal :: a -> ExpectBroken 'Ideal a

unCurrent :: ExpectBroken 'Current a -> a
unCurrent (BrokenCurrent a) = a

-- | Run 'defaultMainWithRerun', limiting each single test case running at most 10 minutes
defaultTestRunner :: TestTree -> IO ()
defaultTestRunner = defaultMainWithRerun . adjustOption (const $ mkTimeout 600000000)
Expand Down Expand Up @@ -903,4 +916,3 @@ kick proxyMsg = do
case fromJSON _params of
Success x -> return x
other -> error $ "Failed to parse kick/done details: " <> show other

Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
Expand Down

0 comments on commit 50d4b0a

Please sign in to comment.