[Haskell-cafe] No instance - but it could just put one in the context
Tom Ellis
tom-lists-haskell-cafe-2013 at jaguarpaw.co.uk
Thu Feb 22 22:39:59 UTC 2018
I'm puzzled by GHC's behaviour in the following program.
'baz = bar . foo' does not work because there is "no instance for ...". But
if I manually assume those instances in the context all is fine. Why can
GHC not infer that context? Is there any extension or clever trick I can
use to get this to infer like I want?
Thanks,
Tom
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
class Foo a b
class Bar a b
type family Quux a
foo :: ( Foo a b
, b ~ Quux a )
=> a
-> Quux a
foo = undefined
bar :: Bar a b
=> a
-> b
bar = undefined
-- Doesn't work
-- No instance for (Bar (Quux a0) c0) arising from a use of ‘bar’
-- No instance for (Foo a0 (Quux a0)) arising from a use of ‘foo’
--baz = bar . foo
baz' :: ( Foo a (Quux a)
, Bar (Quux a) b )
=> a
-> b
baz' = bar . foo
More information about the Haskell-Cafe
mailing list