
I've got a case in a library I'm working on where having -XExtendedDefaultRules with MPTCs would be very, very helpful. Is it possible? I.e., we can now write: ``` {-# LANGUAGE ExtendedDefaultRules #-} data AB = A | B Double deriving (Show) class Foo x where foo :: x -> AB instance Foo Double where foo = B main = print $ foo 5 ``` And -XExtendedDefaultRules makes sure we don't need to write "5 :: Double" If, though, I want 'Foo' to take another parameter (here, a :: [Symbol]), it falls apart: ``` {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} import GHC.TypeLits data AB = A | B Double deriving (Show) class Foo x (a :: [Symbol]) where foo :: x -> AB instance Foo Double a where foo = B main = print $ foo 5 ``` Is there a reason MPTCs can't support ExtendedDefaultRules? Thanks! Tom

Bump -- is this feasible? It would be extremely helpful for an EDSL of mine.
Tom
On Tue, Aug 30, 2016 at 5:23 AM, Tom Murphy
I've got a case in a library I'm working on where having -XExtendedDefaultRules with MPTCs would be very, very helpful. Is it possible?
I.e., we can now write:
``` {-# LANGUAGE ExtendedDefaultRules #-}
data AB = A | B Double deriving (Show)
class Foo x where foo :: x -> AB
instance Foo Double where foo = B
main = print $ foo 5 ```
And -XExtendedDefaultRules makes sure we don't need to write "5 :: Double"
If, though, I want 'Foo' to take another parameter (here, a :: [Symbol]), it falls apart:
``` {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-}
import GHC.TypeLits
data AB = A | B Double deriving (Show)
class Foo x (a :: [Symbol]) where foo :: x -> AB
instance Foo Double a where foo = B
main = print $ foo 5 ```
Is there a reason MPTCs can't support ExtendedDefaultRules?
Thanks! Tom

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExtendedDefaultRules #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
import GHC.TypeLits
data AB = A | B Double deriving (Show)
class Foo x (a :: [Symbol]) where
foo :: x -> AB
instance (b ~ Double) => Foo b a where
foo = B
main = print $ foo 5
On Thu, Sep 22, 2016 at 6:39 PM, Tom Murphy
Bump -- is this feasible? It would be extremely helpful for an EDSL of mine.
Tom
On Tue, Aug 30, 2016 at 5:23 AM, Tom Murphy
wrote: I've got a case in a library I'm working on where having -XExtendedDefaultRules with MPTCs would be very, very helpful. Is it possible?
I.e., we can now write:
``` {-# LANGUAGE ExtendedDefaultRules #-}
data AB = A | B Double deriving (Show)
class Foo x where foo :: x -> AB
instance Foo Double where foo = B
main = print $ foo 5 ```
And -XExtendedDefaultRules makes sure we don't need to write "5 :: Double"
If, though, I want 'Foo' to take another parameter (here, a :: [Symbol]), it falls apart:
``` {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-}
import GHC.TypeLits
data AB = A | B Double deriving (Show)
class Foo x (a :: [Symbol]) where foo :: x -> AB
instance Foo Double a where foo = B
main = print $ foo 5 ```
Is there a reason MPTCs can't support ExtendedDefaultRules?
Thanks! Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Chris Allen Currently working on http://haskellbook.com

With GHC 8.0.1 I get a type error:
error:
• Could not deduce (Foo x a0)
from the context: Foo x a
bound by the type signature for:
foo :: Foo x a => x -> AB
On Fri, Sep 23, 2016 at 8:56 AM, Christopher Allen
{-# LANGUAGE DataKinds #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-}
import GHC.TypeLits
data AB = A | B Double deriving (Show)
class Foo x (a :: [Symbol]) where foo :: x -> AB
instance (b ~ Double) => Foo b a where foo = B
main = print $ foo 5
On Thu, Sep 22, 2016 at 6:39 PM, Tom Murphy
wrote: Bump -- is this feasible? It would be extremely helpful for an EDSL of mine.
Tom
On Tue, Aug 30, 2016 at 5:23 AM, Tom Murphy
wrote: I've got a case in a library I'm working on where having -XExtendedDefaultRules with MPTCs would be very, very helpful. Is it possible?
I.e., we can now write:
``` {-# LANGUAGE ExtendedDefaultRules #-}
data AB = A | B Double deriving (Show)
class Foo x where foo :: x -> AB
instance Foo Double where foo = B
main = print $ foo 5 ```
And -XExtendedDefaultRules makes sure we don't need to write "5 ::
Double"
If, though, I want 'Foo' to take another parameter (here, a ::
[Symbol]),
it falls apart:
``` {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-}
import GHC.TypeLits
data AB = A | B Double deriving (Show)
class Foo x (a :: [Symbol]) where foo :: x -> AB
instance Foo Double a where foo = B
main = print $ foo 5 ```
Is there a reason MPTCs can't support ExtendedDefaultRules?
Thanks! Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Chris Allen Currently working on http://haskellbook.com

Ah, looks like that's unrelated to the original issue, though -- thanks!
Tom
On Fri, Sep 23, 2016 at 9:15 AM, Tom Murphy
With GHC 8.0.1 I get a type error:
error: • Could not deduce (Foo x a0) from the context: Foo x a bound by the type signature for: foo :: Foo x a => x -> AB
On Fri, Sep 23, 2016 at 8:56 AM, Christopher Allen
wrote: {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TypeFamilies #-}
import GHC.TypeLits
data AB = A | B Double deriving (Show)
class Foo x (a :: [Symbol]) where foo :: x -> AB
instance (b ~ Double) => Foo b a where foo = B
main = print $ foo 5
On Thu, Sep 22, 2016 at 6:39 PM, Tom Murphy
wrote: Bump -- is this feasible? It would be extremely helpful for an EDSL of mine.
Tom
On Tue, Aug 30, 2016 at 5:23 AM, Tom Murphy
wrote: I've got a case in a library I'm working on where having -XExtendedDefaultRules with MPTCs would be very, very helpful. Is it possible?
I.e., we can now write:
``` {-# LANGUAGE ExtendedDefaultRules #-}
data AB = A | B Double deriving (Show)
class Foo x where foo :: x -> AB
instance Foo Double where foo = B
main = print $ foo 5 ```
And -XExtendedDefaultRules makes sure we don't need to write "5 ::
Double"
If, though, I want 'Foo' to take another parameter (here, a ::
[Symbol]),
it falls apart:
``` {-# LANGUAGE DataKinds #-} {-# LANGUAGE ExtendedDefaultRules #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MultiParamTypeClasses #-}
import GHC.TypeLits
data AB = A | B Double deriving (Show)
class Foo x (a :: [Symbol]) where foo :: x -> AB
instance Foo Double a where foo = B
main = print $ foo 5 ```
Is there a reason MPTCs can't support ExtendedDefaultRules?
Thanks! Tom
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Chris Allen Currently working on http://haskellbook.com
participants (2)
-
Christopher Allen
-
Tom Murphy