Skip to content
Snippets Groups Projects
Commit 0d36d57b authored by dimitris's avatar dimitris
Browse files

Testcases for floating equalities ouf of implications

and for recording extra untouchable variables.
parent 12e5c1e7
No related merge requests found
{-# LANGUAGE GADTs #-}
module FloatEq where
data T a where
T1 :: T Int
T2 :: T a
h :: T a -> a -> Int
h = undefined
f x y = case x of
T1 -> y::Int
T2 -> h x y
......@@ -111,3 +111,5 @@ test('T5424',
extra_clean(['T5424a.hi', 'T5424a.o']),
multimod_compile,
['T5424', '-v0 -O0'])
test('FloatEq', normal, compile, [''])
\ No newline at end of file
{-# LANGUAGE TypeFamilies, FunctionalDependencies, FlexibleContexts, GADTs, ScopedTypeVariables #-}
module ExtraTcsUntch where
class C x y | x -> y where
op :: x -> y -> ()
instance C [a] [a]
type family F a :: *
h :: F Int -> ()
h = undefined
data TEx where
TEx :: a -> TEx
f (x::beta) =
let g1 :: forall b. b -> ()
g1 _ = h [x]
g2 z = case z of TEx y -> (h [[undefined]], op x [y])
in (g1 '3', g2 undefined)
{- This example comes from Note [Extra TcS Untouchables] in TcSimplify. It demonstrates
why when floating equalities out of an implication constraint we must record the free
variables of the equalities as untouchables. With GHC 7.4.1 this program gives a Core
Lint error because of an existential escaping. -}
ExtraTcsUntch.hs:23:53:
Could not deduce (C [t] [a]) arising from a use of `op'
from the context (beta ~ [t], F Int ~ [[t]])
bound by the inferred type of
f :: (beta ~ [t], F Int ~ [[t]]) => beta -> ((), ((), ()))
at ExtraTcsUntch.hs:(20,1)-(24,29)
Possible fix: add an instance declaration for (C [t] [a])
In the expression: op x [y]
In the expression: (h [[undefined]], op x [y])
In a case alternative: TEx y -> (h [[undefined]], op x [y])
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