[Git][ghc/ghc][wip/hie-file-improvements] hie files: Take evidence for quantified contraints into account when saving...

Zubin pushed to branch wip/hie-file-improvements at Glasgow Haskell Compiler / GHC Commits: d201a2a1 by Zubin Duggal at 2025-06-17T18:13:40+05:30 hie files: Take evidence for quantified contraints into account when saving evidence terms to the hie ast Fixes #25709 - - - - - 3 changed files: - compiler/GHC/Iface/Ext/Ast.hs - + testsuite/tests/hiefile/should_run/T25709.hs - testsuite/tests/hiefile/should_run/all.T Changes: ===================================== compiler/GHC/Iface/Ext/Ast.hs ===================================== @@ -680,7 +680,14 @@ evVarsOfTermList (EvTypeable _ ev) = EvTypeableTyApp e1 e2 -> concatMap evVarsOfTermList [e1,e2] EvTypeableTrFun e1 e2 e3 -> concatMap evVarsOfTermList [e1,e2,e3] EvTypeableTyLit e -> evVarsOfTermList e -evVarsOfTermList (EvFun{}) = [] +evVarsOfTermList (EvFun { et_given = givens, et_binds = EvBinds binds_b, et_body = body_id }) + = let + binds = bagToList binds_b + lhs_evvars = S.fromList $ map evBindVar binds + rhs_evvars = S.fromList $ concatMap (evVarsOfTermList . eb_rhs) binds + in + S.toList $ + ( ( S.insert body_id rhs_evvars ) S.\\ S.fromList givens ) S.\\ lhs_evvars instance ToHie (EvBindContext (LocatedA TcEvBinds)) where toHie (EvBindContext sc sp (L span (EvBinds bs))) ===================================== testsuite/tests/hiefile/should_run/T25709.hs ===================================== @@ -0,0 +1,28 @@ +{-# LANGUAGE QuantifiedConstraints#-} +{-# LANGUAGE UndecidableInstances #-} +module Main where + +import TestUtils +import qualified Data.Map.Strict as M +import qualified Data.Set as S +import Data.Either +import Data.Maybe +import Data.Bifunctor (first) +import GHC.Plugins (moduleNameString, nameStableString, nameOccName, occNameString, isDerivedOccName) +import GHC.Iface.Ext.Types + + +import Data.Typeable + +data Some c where + Some :: c a => a -> Some c + +extractSome :: (Typeable a, forall x. c x => Typeable x) => Some c -> Maybe a +extractSome (Some a) = cast a + +points :: [(Int,Int)] +points = [(21,11)] + +main = do + (df, hf) <- readTestHie "T25709.hie" + undefined ===================================== testsuite/tests/hiefile/should_run/all.T ===================================== @@ -7,4 +7,5 @@ test('SpliceTypes', [req_th, extra_run_opts('"' + config.libdir + '"'), extra_fi test('HieVdq', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info']) test('T23540', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info']) test('T23120', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info']) -test('T24544', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info']) \ No newline at end of file +test('T24544', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info']) +test('T25709', [extra_run_opts('"' + config.libdir + '"'), extra_files(['TestUtils.hs'])], compile_and_run, ['-package ghc -fwrite-ide-info']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d201a2a1b61db54d2a4a5a5ecf0b92f2... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d201a2a1b61db54d2a4a5a5ecf0b92f2... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Zubin (@wz1000)