Skip to content
Snippets Groups Projects
Commit a05d71a7 authored by Simon Peyton Jones's avatar Simon Peyton Jones Committed by Ben Gamari
Browse files

Add a missing zonk in TcDerivInfer.simplifyDeriv

I'm astonished that anything worked without this!

Fixes Trac #14339

(cherry picked from commit 13fdca3d)
parent 913ffc0c
No related merge requests found
......@@ -622,6 +622,8 @@ simplifyDeriv pred tvs thetas
-- Simplify the constraints
; solved_implics <- runTcSDeriveds $ solveWantedsAndDrop
$ unionsWC wanteds
-- It's not yet zonked! Obviously zonk it before peering at it
; solved_implics <- zonkWC solved_implics
-- See [STEP DAC HOIST]
-- Split the resulting constraints into bad and good constraints,
......
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE UndecidableInstances #-}
module Bug where
import GHC.TypeLits
newtype Baz = Baz Foo
deriving Bar
newtype Foo = Foo Int
class Bar a where
bar :: a
instance (TypeError (Text "Boo")) => Bar Foo where
bar = undefined
......@@ -89,3 +89,4 @@ test('T13272', normal, compile, [''])
test('T13272a', normal, compile, [''])
test('T13297', normal, compile, [''])
test('T14331', normal, compile, [''])
test('T14339', normal, compile, [''])
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