i am trying to address part of #1617 (optionally restoring the old :browse, as :browse!, listing class methods and data constructors separately, not just in context). in principle, that is straightforward, but for the type of class methods - what function prints them correctly?

method types seem to reflect the implementation type (with the class dictionary treated separately) rather than the user type (with the class predicate being just one part of the context):

   *Main> :set -fglasgow-exts
   *Main> :b Control.Monad    -- original
   class Monad m where
     (>>=) :: forall a b. m a -> (a -> m b) -> m b
     (>>) :: forall a b. m a -> m b -> m b
     return :: forall a. a -> m a
     fail :: forall a. String -> m a
   ..
   *Main> :b! Control.Monad    -- added variant
   fail :: forall (m :: * -> *). (Monad m) => forall a. String -> m a
   (>>=) ::
     forall (m :: * -> *).
     (Monad m) =>
     forall a b. m a -> (a -> m b) -> m b
   (>>) ::
     forall (m :: * -> *). (Monad m) => forall a b. m a -> m b -> m b
   return :: forall (m :: * -> *). (Monad m) => forall a. a -> m a
   class Monad m where
     (>>=) :: forall a b. m a -> (a -> m b) -> m b
     (>>) :: forall a b. m a -> m b -> m b
     return :: forall a. a -> m a
     fail :: forall a. String -> m a
   ..

this doesn't look too bad, simply using pprTyThing instead of pprTyThingInContext, and not filtering out children.

however, things go wrong if i try not to show the foralls, by stripping the
outermost forall. first, there are actually two levels of forall, and second, the class appears as a parameter rather than context (i thought printing
was controlled by finding a predicate to the left of a function arrow, but
since Type is not in Show, i can't easily check the actual representation):

   *Main> :b! Control.Monad
   fail :: Monad m -> forall a. String -> m a
   (>>=) :: Monad m -> forall a b. m a -> (a -> m b) -> m b
   (>>) :: Monad m -> forall a b. m a -> m b -> m b
   return :: Monad m -> forall a. a -> m a
   class Monad m where
     (>>=) :: m a -> (a -> m b) -> m b
     (>>) :: m a -> m b -> m b
     return :: a -> m a
     fail :: String -> m a
   ..

also, if the class method has its own context, as in:

   class C a where  c :: Num b => a -> b

we get two levels of context, instead of a single merged context:

   *Main> :b! Main
   class C a where c :: (Num b) => a -> b
   c :: C a -> forall b. (Num b) => a -> b

   *Main> :set -fglasgow-exts

   *Main> :b! Main
   class C a where c :: forall b. (Num b) => a -> b
   c :: forall a. (C a) => forall b. (Num b) => a -> b

is there a proper way of printing those types? to identify class methods,
i can use GHC.isClassOpId_maybe, but then the only options i have
found so far are: use GHC.exprType (awkward), or re-assemble the
foralls and contexts at the front, using the various split type operations (awkward and potentially error-prone). there has to be a better way.

my patch history doesn't seem to go that far back, but how was this
handled before :browse started printing things in context only?

claus

_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to