Skip to content

Commit

Permalink
Refine ASSERT in buildPatSyn for the nullary case.
Browse files Browse the repository at this point in the history
For a nullary pattern synonym we add an extra void argument to the
matcher in order to preserve laziness. The check in buildPatSyn
wasn't aware of this special case which was causing the assertion to
fail.

Reviewers: austin, simonpj, bgamari

Reviewed By: simonpj, bgamari

Subscribers: simonpj, thomie

Differential Revision: https://phabricator.haskell.org/D2624

GHC Trac Issues: #12746
  • Loading branch information
mpickering authored and bgamari committed Oct 26, 2016
1 parent 488a9ed commit 23143f6
Show file tree
Hide file tree
Showing 4 changed files with 24 additions and 2 deletions.
13 changes: 11 additions & 2 deletions compiler/iface/BuildTyCl.hs
Expand Up @@ -18,6 +18,7 @@ module BuildTyCl (
import IfaceEnv
import FamInstEnv( FamInstEnvs, mkNewTypeCoAxiom )
import TysWiredIn( isCTupleTyConName )
import TysPrim ( voidPrimTy )
import DataCon
import PatSyn
import Var
Expand Down Expand Up @@ -247,7 +248,7 @@ buildPatSyn src_name declared_infix matcher@(matcher_id,_) builder
, pat_ty `eqType` substTy subst pat_ty1
, prov_theta `eqTypes` substTys subst prov_theta1
, req_theta `eqTypes` substTys subst req_theta1
, arg_tys `eqTypes` substTys subst arg_tys1
, compareArgTys arg_tys (substTys subst arg_tys1)
])
, (vcat [ ppr univ_tvs <+> twiddle <+> ppr univ_tvs1
, ppr ex_tvs <+> twiddle <+> ppr ex_tvs1
Expand All @@ -263,11 +264,19 @@ buildPatSyn src_name declared_infix matcher@(matcher_id,_) builder
((_:_:univ_tvs1), req_theta1, tau) = tcSplitSigmaTy $ idType matcher_id
([pat_ty1, cont_sigma, _], _) = tcSplitFunTys tau
(ex_tvs1, prov_theta1, cont_tau) = tcSplitSigmaTy cont_sigma
(arg_tys1, _) = tcSplitFunTys cont_tau
(arg_tys1, _) = (tcSplitFunTys cont_tau)
twiddle = char '~'
subst = zipTvSubst (univ_tvs1 ++ ex_tvs1)
(mkTyVarTys (binderVars (univ_tvs ++ ex_tvs)))

-- For a nullary pattern synonym we add a single void argument to the
-- matcher to preserve laziness in the case of unlifted types.
-- See #12746
compareArgTys :: [Type] -> [Type] -> Bool
compareArgTys [] [x] = x `eqType` voidPrimTy
compareArgTys arg_tys matcher_arg_tys = arg_tys `eqTypes` matcher_arg_tys


------------------------------------------------------
type TcMethInfo -- A temporary intermediate, to communicate
-- between tcClassSigs and buildClass.
Expand Down
7 changes: 7 additions & 0 deletions testsuite/tests/patsyn/should_compile/T12746.hs
@@ -0,0 +1,7 @@
module T12746 where

import T12746A

foo a = case a of
Foo -> True
_ -> False
5 changes: 5 additions & 0 deletions testsuite/tests/patsyn/should_compile/T12746A.hs
@@ -0,0 +1,5 @@
{-# LANGUAGE ScopedTypeVariables, PatternSynonyms #-}
module T12746A where

pattern Foo :: Int
pattern Foo = 0x00000001
1 change: 1 addition & 0 deletions testsuite/tests/patsyn/should_compile/all.T
Expand Up @@ -61,3 +61,4 @@ test('T12484', normal, compile, [''])
test('T11987', normal, multimod_compile, ['T11987', '-v0'])
test('T12615', normal, compile, [''])
test('T12698', normal, compile, [''])
test('T12746', normal, multi_compile, ['T12746', [('T12746A.hs', '-c')],'-v0'])

0 comments on commit 23143f6

Please sign in to comment.