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 -> ABOn Fri, Sep 23, 2016 at 8:56 AM, Christopher Allen <cma@bitemyapp.com> 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 <amindfv@gmail.com> 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 <amindfv@gmail.com> 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-caf e
> Only members subscribed via the mailman list are allowed to post.
--
Chris Allen
Currently working on http://haskellbook.com