Why base 4.4.0.0 does not use default signatures extention (new in GHC 7.2)?

Hello, While reading the list of changes in GHC 7.2 I noticed that default signatures extention have been added. Therefore following code compiles:
{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE DefaultSignatures #-} class Functor f where fmap :: (a -> b) -> f a -> f b default fmap :: Applicative f => (a -> b) -> f a -> f b f `fmap` m = pure f <*> m (<$) :: a -> f b -> f a (<$) = fmap . const
(<$>) = fmap
class Functor f => Pointed f where point :: a -> f a default point :: Applicative f => a -> f a point = pure
class Pointed f => Applicative f where pure :: a -> f a default pure :: Monad f => a -> f a pure = return (<*>) :: f (a -> b) -> f a -> f b default (<*>) :: Monad f => f (a -> b) -> f a -> f b f <*> v = liftM2 ($) f v (*>) :: f a -> f b -> f b (*>) = liftA2 (const id) (<*) :: f a -> f b -> f a (<*) = liftA2 const
class Applicative f => Monad f where return :: a -> f a (>>=) :: f a -> (a -> f b) -> f b (>>) :: f a -> f b -> f b m >> k = m >>= const k
data List a = Empty | Cons a (List a)
instance Monad List where return x = Cons x Empty Empty >>= _ = Empty Cons x xs >>= f = Cons (f x) (xs >>= f)
test = Empty <*> Empty
($) = \f v -> f v liftA2 f a b = f <$> a <*> b liftM2 f a b = f >>= \f' -> a >>= \a' -> b >>= \b'-> return (f' a' b') const a _ = a fix f = let x = f x in x error _ = fix id id x = x f . g = \x -> f (g x)
While the Functor f => (Pointed f =>) Applicative f => Monad f is still discussed the default methods would be a step towards the goal. Regards

On Thu, Sep 22, 2011 at 00:18, Maciej Marcin Piechotka < uzytkownik2@gmail.com> wrote:
While the Functor f => (Pointed f =>) Applicative f => Monad f is still discussed the default methods would be a step towards the goal.
Adding support in the compiler is the first step. ghc doesn't own the libraries process, which is where the second step happens. Now that the compiler support is there, a (formal) change request is appropriate. -- brandon s allbery allbery.b@gmail.com wandering unix systems administrator (available) (412) 475-9364 vm/sms

On 22 September 2011 06:18, Maciej Marcin Piechotka
While the Functor f => (Pointed f =>) Applicative f => Monad f is still discussed the default methods would be a step towards the goal.
I like it. It's indeed a good step towards: http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances Why not formally propose this? Regards, Bas

On Fri, 2011-09-23 at 14:46 +0200, Bas van Dijk wrote:
On 22 September 2011 06:18, Maciej Marcin Piechotka
wrote: While the Functor f => (Pointed f =>) Applicative f => Monad f is still discussed the default methods would be a step towards the goal.
I like it. It's indeed a good step towards:
http://hackage.haskell.org/trac/ghc/wiki/DefaultSuperclassInstances
Why not formally propose this?
Done
Regards,
Bas
Regards
participants (3)
-
Bas van Dijk
-
Brandon Allbery
-
Maciej Marcin Piechotka