Skip to content

Commit cb9a38b

Browse files
authored
Merge pull request #508 from konn/tactic-exclude-coercions
Makes dictionary argument exclusion logic in Tactic plugin more robust
2 parents 56ff141 + 01110c8 commit cb9a38b

File tree

5 files changed

+49
-8
lines changed

5 files changed

+49
-8
lines changed

plugins/tactics/src/Ide/Plugin/Tactic/CodeGen.hs

+25-7
Original file line numberDiff line numberDiff line change
@@ -23,6 +23,7 @@ import GHC.SourceGen.Binds
2323
import GHC.SourceGen.Expr
2424
import GHC.SourceGen.Overloaded
2525
import GHC.SourceGen.Pat
26+
import Ide.Plugin.Tactic.GHC
2627
import Ide.Plugin.Tactic.Judgements
2728
import Ide.Plugin.Tactic.Machinery
2829
import Ide.Plugin.Tactic.Naming
@@ -120,13 +121,30 @@ unzipTrace l =
120121

121122

122123
-- | Essentially same as 'dataConInstOrigArgTys' in GHC,
123-
-- but we need some tweaks in GHC >= 8.8.
124-
-- Since old 'dataConInstArgTys' seems working with >= 8.8,
125-
-- we just filter out non-class types in the result.
126-
dataConInstOrigArgTys' :: DataCon -> [Type] -> [Type]
127-
dataConInstOrigArgTys' con ty =
128-
let tys0 = dataConInstArgTys con ty
129-
in filter (maybe True (not . isClassTyCon) . tyConAppTyCon_maybe) tys0
124+
-- but only accepts universally quantified types as the second arguments
125+
-- and automatically introduces existentials.
126+
--
127+
-- NOTE: The behaviour depends on GHC's 'dataConInstOrigArgTys'.
128+
-- We need some tweaks if the compiler changes the implementation.
129+
dataConInstOrigArgTys'
130+
:: DataCon
131+
-- ^ 'DataCon'structor
132+
-> [Type]
133+
-- ^ /Universally/ quantified type arguments to a result type.
134+
-- It /MUST NOT/ contain any dictionaries, coercion and existentials.
135+
--
136+
-- For example, for @MkMyGADT :: b -> MyGADT a c@, we
137+
-- must pass @[a, c]@ as this argument but not @b@, as @b@ is an existential.
138+
-> [Type]
139+
-- ^ Types of arguments to the DataCon with returned type is instantiated with the second argument.
140+
dataConInstOrigArgTys' con uniTys =
141+
let exvars = dataConExTys con
142+
in dataConInstOrigArgTys con $
143+
uniTys ++ fmap mkTyVarTy exvars
144+
-- Rationale: At least in GHC <= 8.10, 'dataConInstOrigArgTys'
145+
-- unifies the second argument with DataCon's universals followed by existentials.
146+
-- If the definition of 'dataConInstOrigArgTys' changes,
147+
-- this place must be changed accordingly.
130148

131149
------------------------------------------------------------------------------
132150
-- | Combinator for performing case splitting, and running sub-rules on the

plugins/tactics/src/Ide/Plugin/Tactic/GHC.hs

+7-1
Original file line numberDiff line numberDiff line change
@@ -9,6 +9,7 @@ import Control.Monad.State
99
import qualified Data.Map as M
1010
import Data.Maybe (isJust)
1111
import Data.Traversable
12+
import qualified DataCon as DataCon
1213
import Development.IDE.GHC.Compat
1314
import Generics.SYB (mkT, everywhere)
1415
import Ide.Plugin.Tactic.Types
@@ -20,7 +21,6 @@ import TysWiredIn (intTyCon, floatTyCon, doubleTyCon, charTyCon)
2021
import Unique
2122
import Var
2223

23-
2424
tcTyVar_maybe :: Type -> Maybe Var
2525
tcTyVar_maybe ty | Just ty' <- tcView ty = tcTyVar_maybe ty'
2626
tcTyVar_maybe (CastTy ty _) = tcTyVar_maybe ty -- look through casts, as
@@ -148,3 +148,9 @@ getPatName (fromPatCompat -> p0) =
148148
#endif
149149
_ -> Nothing
150150

151+
dataConExTys :: DataCon -> [TyCoVar]
152+
#if __GLASGOW_HASKELL__ >= 808
153+
dataConExTys = DataCon.dataConExTyCoVars
154+
#else
155+
dataConExTys = DataCon.dataConExTyVars
156+
#endif

test/functional/Tactic.hs

+1
Original file line numberDiff line numberDiff line change
@@ -104,6 +104,7 @@ tests = testGroup
104104
, goldenTest "GoldenSwap.hs" 2 8 Auto ""
105105
, goldenTest "GoldenFmapTree.hs" 4 11 Auto ""
106106
, goldenTest "GoldenGADTDestruct.hs" 7 17 Destruct "gadt"
107+
, goldenTest "GoldenGADTDestructCoercion.hs" 8 17 Destruct "gadt"
107108
, goldenTest "GoldenGADTAuto.hs" 7 13 Auto ""
108109
, goldenTest "GoldenSwapMany.hs" 2 12 Auto ""
109110
, goldenTest "GoldenBigTuple.hs" 4 12 Auto ""
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
{-# LANGUAGE RankNTypes #-}
2+
{-# LANGUAGE GADTs #-}
3+
module GoldenGADTDestruct where
4+
data E a b where
5+
E :: forall a b. (b ~ a, Ord a) => b -> E a [a]
6+
7+
ctxGADT :: E a b -> String
8+
ctxGADT gadt = _decons
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,8 @@
1+
{-# LANGUAGE RankNTypes #-}
2+
{-# LANGUAGE GADTs #-}
3+
module GoldenGADTDestruct where
4+
data E a b where
5+
E :: forall a b. (b ~ a, Ord a) => b -> E a [a]
6+
7+
ctxGADT :: E a b -> String
8+
ctxGADT gadt = (case gadt of { (E b) -> _ })

0 commit comments

Comments
 (0)