On 03/12/12 20:13, Iavor Diatchki wrote:
Hello,
On Mon, Dec 3, 2012 at 8:44 AM, Simon Marlow <marlo...@gmail.com
<mailto:marlo...@gmail.com>> wrote:
OI know that Accessor has an Applicative instace because the operations
work. I'd like to find the instance, so I can see how it works,
so I try:
Ok, so this is a bug: you shouldn't be able to use the instance
because it isn't in scope. If this was a source file, then GHC
would complain that the instance was not in scope.
The bug is (sort of) documented in the "Known Bugs" section of the
user guide, although the documentation incorrectly says that it also
affects --make, which it doesn't (I'll fix it).
I don't think that this is the bug to blame: the instance is in scope,
it is just that it is being filtered by ":info".
Here is an example:
module Test where
import Control.Applicative (pure)
import Control.Lens
example :: Accessor () ()
example = pure ()
This works just fine. I think the issue is as follows. The
`Applicative` instance for `Accessor` is like this:
instance Monoid r => Applicative (Accessor r)
Now, on the GHCi command line `Accessor` and `Applicative` are in scope
but `Monoid` is not. However, there are instances of `Monoid` for
various datatypes (e.g., ()) that are also in scope, so that instance is
actually usable.
Ah, I see. Sp that suggests a better fix: the new :info! should display
all instances that are in scope, in contrast to the ordinary :info which
displays only instances involving types and classes that are in scope.
As far as I understand, the current plausiblity check filters out any
instances that contain tycons that are not in-scope, which is why this
particular instance does not show up. It looks like in some cases this
is too aggressive.
So I don't really object to having this "feature", as long as we say
clearly in the documentation that it doesn't have a well-specified
behaviour, and the instances it shows may or may not actually be
available. (if we fix the bug, many of them won't be available, but
it might be useful to find out where to get them from).
Would you mind updating the docs, and close #5998?
Yeah, I'd be happy to do that. Which documentation should I update?
The GHCi docs (docs/users_guide/ghci.xml) to add the new command.
Cheers,
Simon
-Iavor
Cheers,
Simon
Prelude Control.Applicative Control.Lens> :i Accessor
newtype Accessor r a
= Control.Lens.Internal.Accessor
{Control.Lens.Internal.__runAccessor :: r}
-- Defined in `Control.Lens.Internal'
instance Functor (Accessor r) -- Defined in `Control.Lens.Internal'
instance Gettable (Accessor r)
-- Defined in `Control.Lens.Internal’
Weird, it doesn’t show up, so what are the instances of
`Applicative`?
Prelude Control.Applicative Control.Lens> :i Applicative
class Functor f => Applicative f where
pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
(*>) :: f a -> f b -> f b
(<*) :: f a -> f b -> f a
-- Defined in `Control.Applicative'
instance Applicative [] -- Defined in `Control.Applicative'
instance Applicative ZipList -- Defined in `Control.Applicative'
instance Monad m => Applicative (WrappedMonad m)
-- Defined in `Control.Applicative'
instance Applicative Maybe -- Defined in `Control.Applicative'
instance Applicative IO -- Defined in `Control.Applicative'
instance Applicative (Either e) -- Defined in `Control.Applicative'
instance Applicative ((->) a) -- Defined in `Control.Applicative'
instance Applicative Mutator -- Defined in `Control.Lens.Internal'
instance Applicative (Bazaar a b)
-- Defined in `Control.Lens.Internal’
It does not show up, but I'm sure that there is an instance as the
operations seem to work! It turns out that the only way to find the
instance is to not only already know that there is one and
import the
appropriate module, but to also import the modules used in the
context.
But if I already knew all of this I wouldn't have asked GHCi.
Prelude Control.Applicative Control.Lens> import Data.Monoid
Prelude Control.Applicative Control.Lens Data.Monoid> :i Accessor
newtype Accessor r a
= Control.Lens.Internal.Accessor
{Control.Lens.Internal.__runAccessor :: r}
-- Defined in `Control.Lens.Internal'
instance Functor (Accessor r) -- Defined in `Control.Lens.Internal'
*instance Monoid r => Applicative (Accessor r)*
-- Defined in `Control.Lens.Internal'
instance Gettable (Accessor r)
-- Defined in `Control.Lens.Internal'
In contrast, with ":info!" we get everything that GHCi knows
about, so
it is quite easy to figure out what's going on.
-Iavor
On Fri, Nov 30, 2012 at 3:42 AM, Simon Marlow
<marlo...@gmail.com <mailto:marlo...@gmail.com>
<mailto:marlo...@gmail.com <mailto:marlo...@gmail.com>>> wrote:
On 30/11/12 02:03, Iavor Diatchki wrote:
Repository : ssh://darcs.haskell.org//srv/____darcs/ghc
<http://darcs.haskell.org//srv/__darcs/ghc>
<http://darcs.haskell.org//__srv/darcs/ghc
<http://darcs.haskell.org//srv/darcs/ghc>>
On branch : master
http://hackage.haskell.org/____trac/ghc/changeset/____2ec32a8e1cb323b230b0c228dbee31____3647892bf4
<http://hackage.haskell.org/__trac/ghc/changeset/__2ec32a8e1cb323b230b0c228dbee31__3647892bf4>
<http://hackage.haskell.org/__trac/ghc/changeset/__2ec32a8e1cb323b230b0c228dbee31__3647892bf4
<http://hackage.haskell.org/trac/ghc/changeset/2ec32a8e1cb323b230b0c228dbee313647892bf4>>
------------------------------____----------------------------__--__---
commit 2ec32a8e1cb323b230b0c228dbee31____3647892bf4
Author: Iavor S. Diatchki <diatc...@galois.com
<mailto:diatc...@galois.com>
<mailto:diatc...@galois.com <mailto:diatc...@galois.com>>>
Date: Thu Nov 29 17:14:48 2012 -0800
Add ":info!" to GHCi. This shows all instances
without
filtering first.
The default behavior of :info is to show only those
instances of
for a type, where all relevant type constructor
names are
in scope.
This keeps down the number of instances shown to
the user.
In some cases, it is nice to be able to see all
instances
for a type.
This patch implements this with the :info! command.
Was there some discussion about this? The last I remember
was this:
http://hackage.haskell.org/____trac/ghc/ticket/5998
<http://hackage.haskell.org/__trac/ghc/ticket/5998>
<http://hackage.haskell.org/__trac/ghc/ticket/5998
<http://hackage.haskell.org/trac/ghc/ticket/5998>>
where we decided not to implement this because it is
essentially a
random UI: the behaviour can't be described sensibly because it
depends on which interface files GHC happens to have seen
so far.
There's also this:
http://hackage.haskell.org/____trac/ghc/ticket/3080
<http://hackage.haskell.org/__trac/ghc/ticket/3080>
<http://hackage.haskell.org/__trac/ghc/ticket/3080
<http://hackage.haskell.org/trac/ghc/ticket/3080>>
which looks like a duplicate (I just closed it).
Cheers,
Simon
___________________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org <mailto:Cvs-ghc@haskell.org>
<mailto:Cvs-ghc@haskell.org <mailto:Cvs-ghc@haskell.org>>
http://www.haskell.org/____mailman/listinfo/cvs-ghc
<http://www.haskell.org/__mailman/listinfo/cvs-ghc>
<http://www.haskell.org/__mailman/listinfo/cvs-ghc
<http://www.haskell.org/mailman/listinfo/cvs-ghc>>
_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc