Skip to content

Commit 0d383dd

Browse files
committed
1 parent 475870d commit 0d383dd

File tree

2 files changed

+20
-2
lines changed

2 files changed

+20
-2
lines changed

liquidhaskell-boot/src/Language/Haskell/Liquid/Types/PredType.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -192,8 +192,9 @@ dcWrapSpecType allowTC dc (DataConP _ _ vs ps cs yts rt _ _ _)
192192
ts' = map ("" , classRFInfo allowTC , , mempty) cs ++ yts'
193193
subst = F.mkSubst [(x, F.EVar y) | (x, y) <- zip as bs]
194194
rt' = F.subst subst rt
195-
makeVars = zipWith (\v a -> RTVar v (rTVarInfo a :: RTVInfo RSort)) vs (fst $ splitForAllTyCoVars $ dataConRepType dc)
196-
makeVars' = map (, mempty) makeVars
195+
makeVars = filter (`elem` fvs) $ zipWith (\v a -> RTVar v (rTVarInfo a :: RTVInfo RSort)) vs (fst $ splitForAllTyCoVars $ dataConRepType dc)
196+
makeVars' = map (, mempty) makeVars
197+
fvs = freeTyVars $ mkArrow [] ps ts' rt'
197198

198199
instance PPrint TyConP where
199200
pprintTidy k tc = "data" <+> pprintTidy k (tcpCon tc)

tests/pos/T2349.hs

Lines changed: 17 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
{-# LANGUAGE GADTs #-}
2+
{-@ LIQUID "--reflection" @-}
3+
module TestModule where
4+
5+
data Expr t where
6+
I :: Int -> Expr Int
7+
8+
NIL :: Expr [t]
9+
CONS :: Int -> Expr t -> Expr [t] -> Expr [t]
10+
11+
{-@
12+
data Expr t where
13+
I :: Int -> Expr Int
14+
NIL :: Expr {v:[t] | len v = 0}
15+
CONS :: xxxxx:_ -> head:Expr t -> tail:Expr {v:[t] | len v = xxxxx} ->
16+
Expr {v:[t] | len v = xxxxx+1}
17+
@-}

0 commit comments

Comments
 (0)