Skip to content
Snippets Groups Projects
Commit 6074cc3c authored by Ackerman's avatar Ackerman Committed by Marge Bot
Browse files

Add failing test case for #23492

parent 03f941f4
No related branches found
No related tags found
No related merge requests found
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE DuplicateRecordFields #-}
module Main where
import TestUtils
import qualified Data.Map as M
import Data.Foldable
-- regression test for https://gitlab.haskell.org/ghc/ghc/-/issues/23492
data PartialFieldSelector
= NoFields
| PartialField { a :: Bool }
-- ^
-- 1
f :: PartialFieldSelector -> Bool
f x = a x
-- ^
-- 2
g :: PartialFieldSelector -> Bool
g x = x.a
-- ^^^
-- 345
p1, p2, p3, p4, p5 :: (Int,Int)
p1 = (13,20)
p2 = (18,7)
p3 = (23,7)
p4 = (23,8)
p5 = (23,9)
selectPoint' :: HieFile -> (Int,Int) -> HieAST Int
selectPoint' hf loc =
maybe (error "point not found") id $ selectPoint hf loc
main = do
(df, hf) <- readTestHie "T23492.hie"
forM_ [p1,p2,p3,p4,p5] $ \point -> do
putStr $ "At " ++ show point ++ ", got type: "
let types = concatMap nodeType $ getSourcedNodeInfo $ sourcedNodeInfo $ selectPoint' hf point
forM_ types $ \typ -> do
putStrLn (renderHieType df $ recoverFullType typ (hie_types hf))
At (13,20), got type: PartialFieldSelector -> Bool
Addr#
Bool
PartialFieldSelector
Addr# -> Bool
forall a. Addr# -> a
At (18,7), got type: PartialFieldSelector -> Bool
At (23,7), got type: PartialFieldSelector
At (23,8), got type: PartialFieldSelector
At (23,9), got type: Bool
test('PatTypes', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info'])
test('HieQueries', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info'])
test('T20341', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info'])
test('T23492', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info'])
test('RecordDotTypes', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info'])
test('SpliceTypes', [req_th, extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info'])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment