Re: Issue with type families

2010-03-03 Thread Daniel Fischer
Am Donnerstag 04 März 2010 02:39:30 schrieb Tyson Whitehead:
> On March 3, 2010 18:35:26 Daniel Fischer wrote:
> > Because:
> >
> > instance Applicative ((->) a) -- Defined in Control.Applicative
> >
> > so, from the instance Z (a -> b), with b == c -> d, we have an
> >
> > instance Z (a -> (b -> c))
> >
> > and from instance Z (m (u -> v)), we have, with m == ((->) x), an
> >
> > instance Z (x -> (u -> v))
>
> Thanks Daniel,
>
> That makes sense.  Strangely enough though, I had actually originally
> tried it with my own Applicative class just in case I was being tripped
> up by something like the (->) instance you pointed out, and it still
> didn't work.

Well, GHC takes only the class head into account for instance selection, 
and

u -> (v -> w)

matches both,

a -> b   --  (a == u, b == v -> w)

and

m (c -> d)-- (m == ((->) u), c == v, d == w),

so there's the overlap without any other type classes involved.
And since u -> (v -> w) matches both instance heads,

type W (u -> (v -> w)) = u -> (v -> w)

and

type W (((->) u) (v -> w)) = (u -> v) -> (u -> w)

are indeed conflicting, so you can't even use OverlappingInstances etc. to 
make it work.

> That is
>
>   {-# LANGUAGE FlexibleInstances, TypeFamilies #-}
>
>   newtype I a = I a
>
>   class A t where
>   ap :: t (a -> b) -> t a -> t b
>
>   class Z t where
>   type W t
>   z :: t -> W t
>
>   instance A I where
>   ap (I f) (I x) = I $ f x
>
>   instance Z (a -> b) where
>   type W (a -> b) = a -> b
>   z = id
>
>   instance A t => Z (t (a -> b)) where
>   type W (t (a -> b)) = t a -> t b
>   z = ap
>
> also gives me
>
>   Temp.hs:17:9:
>   Conflicting family instance declarations:
> type instance W (a -> b) -- Defined at Temp.hs:17:9
> type instance W (t (a -> b)) -- Defined at Temp.hs:21:9
>   Failed, modules loaded: none.
>
> Is the compiler somehow anticipating that I could add an instance for
> (->) to A and thus be back to the Applicative class situation?

The compiler works on an open-world assumption, if the kinds match, there 
could be an instance defined somewhere.

>
> Thanks!  -Tyson
>
> PS:  I asked this here because type classes is a GHC issue, would the
> haskell- cafe list been a more appropriate place?

Either is fine.

Cheers,
Daniel

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Issue with type families

2010-03-03 Thread Tyson Whitehead
On March 3, 2010 18:35:26 Daniel Fischer wrote:
> Because:
>
> instance Applicative ((->) a) -- Defined in Control.Applicative
>
> so, from the instance Z (a -> b), with b == c -> d, we have an
>
> instance Z (a -> (b -> c))
>
> and from instance Z (m (u -> v)), we have, with m == ((->) x), an
>
> instance Z (x -> (u -> v))

Thanks Daniel,

That makes sense.  Strangely enough though, I had actually originally tried it 
with my own Applicative class just in case I was being tripped up by something 
like the (->) instance you pointed out, and it still didn't work.  That is

  {-# LANGUAGE FlexibleInstances, TypeFamilies #-}

  newtype I a = I a

  class A t where
  ap :: t (a -> b) -> t a -> t b

  class Z t where
  type W t
  z :: t -> W t

  instance A I where
  ap (I f) (I x) = I $ f x 

  instance Z (a -> b) where
  type W (a -> b) = a -> b
  z = id

  instance A t => Z (t (a -> b)) where
  type W (t (a -> b)) = t a -> t b
  z = ap

also gives me

  Temp.hs:17:9:
  Conflicting family instance declarations:
type instance W (a -> b) -- Defined at Temp.hs:17:9
type instance W (t (a -> b)) -- Defined at Temp.hs:21:9
  Failed, modules loaded: none.

Is the compiler somehow anticipating that I could add an instance for (->) to 
A and thus be back to the Applicative class situation?

Thanks!  -Tyson

PS:  I asked this here because type classes is a GHC issue, would the haskell-
cafe list been a more appropriate place?


signature.asc
Description: This is a digitally signed message part.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Issue with type families

2010-03-03 Thread Daniel Fischer
Am Donnerstag 04 März 2010 00:17:09 schrieb Tyson Whitehead:
> The following code
>
>   {-# LANGUAGE FlexibleInstances, TypeFamilies #-}
>
>   import Control.Applicative
>
>   class Z t where
>   type W t
>   z :: t -> W t
>
>   instance Z (a -> b) where
>   type W (a -> b) = a -> b
>   z = id
>
>   instance Z (IO (a -> b)) where
>   type W (IO (a -> b)) = IO a -> IO b
>   z = (<*>)
>
> works fine, but if I try and generalize to from IO to the Applicative
> classes
>
>   instance (Applicative m) => Z (m (a -> b)) where
>   type W (m (a -> b)) = m a -> m b
>   z = (<*>)
>
> I get the following error
>
>   Temp.hs:10:9:
>   Conflicting family instance declarations:
> type instance W (a -> b) -- Defined at Temp.hs:10:9
> type instance W (m (a -> b)) -- Defined at Temp.hs:14:9
>   Failed, modules loaded: none.
>
> unless I remove one of the instances, and then it is happy.
>
> Is this correct?  I don't claim to really understand the rules regarding
> type classes, but I can't see why these are overlapping.
>
> Thanks!  -Tyson

Because:

instance Applicative ((->) a) -- Defined in Control.Applicative

so, from the instance Z (a -> b), with b == c -> d, we have an 

instance Z (a -> (b -> c))

and from instance Z (m (u -> v)), we have, with m == ((->) x), an

instance Z (x -> (u -> v))

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Issue with type families

2010-03-03 Thread Tyson Whitehead
The following code

  {-# LANGUAGE FlexibleInstances, TypeFamilies #-}

  import Control.Applicative

  class Z t where
  type W t
  z :: t -> W t

  instance Z (a -> b) where
  type W (a -> b) = a -> b
  z = id

  instance Z (IO (a -> b)) where
  type W (IO (a -> b)) = IO a -> IO b
  z = (<*>)

works fine, but if I try and generalize to from IO to the Applicative classes

  instance (Applicative m) => Z (m (a -> b)) where
  type W (m (a -> b)) = m a -> m b
  z = (<*>)

I get the following error

  Temp.hs:10:9:
  Conflicting family instance declarations:
type instance W (a -> b) -- Defined at Temp.hs:10:9
type instance W (m (a -> b)) -- Defined at Temp.hs:14:9
  Failed, modules loaded: none.

unless I remove one of the instances, and then it is happy.

Is this correct?  I don't claim to really understand the rules regarding type 
classes, but I can't see why these are overlapping.

Thanks!  -Tyson
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: stg-ap-1-upd-info

2010-03-03 Thread Thomas Schilling
I think it means you're created lots of thunks of the form (f x).
Perhaps some foldl vs foldl' issue?  If you're not using foldl
anywhere, look at tail recursive functions and try and make their
accumulators strict.

HTH

On 3 March 2010 16:11, Herk, Robert van  wrote:
> Hi All,
>
> I am optimizing a program to consume less memory.
>
> If I profile it with  +RTS -hd, it reports to fill 50% of my memory with 
> stg-ap-1-upd-info.
>
> Does this mean anything?
>
> Regards,
> Robert
>
> The information contained in this message may be confidential and legally 
> protected under applicable law. The message is intended solely for the 
> addressee(s). If you are not the intended recipient, you are hereby notified 
> that any use, forwarding, dissemination, or reproduction of this message is 
> strictly prohibited and may be unlawful. If you are not the intended 
> recipient, please contact the sender by return e-mail and destroy all copies 
> of the original message.
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>



-- 
Push the envelope.  Watch it bend.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


stg-ap-1-upd-info

2010-03-03 Thread Herk, Robert van
Hi All,

I am optimizing a program to consume less memory.

If I profile it with  +RTS -hd, it reports to fill 50% of my memory with 
stg-ap-1-upd-info.

Does this mean anything?

Regards,
Robert

The information contained in this message may be confidential and legally 
protected under applicable law. The message is intended solely for the 
addressee(s). If you are not the intended recipient, you are hereby notified 
that any use, forwarding, dissemination, or reproduction of this message is 
strictly prohibited and may be unlawful. If you are not the intended recipient, 
please contact the sender by return e-mail and destroy all copies of the 
original message.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: I accidentally the Prelude

2010-03-03 Thread Yitzchak Gale
I wrote:
>> I was suggesting that whenever the Prelude fails to load,
>> the error message should contain that hint.

> hmm, I'll think about that. Is it not enough to see a compilation error
> pointing to the file Prelude.hs?

Seems obvious in the context of this thread. But not being in
the middle of reading the thread, I am certain that this hint
would save me a lot of time and anguish. And it clearly
would have done the same for Josef.

> it's probably not that bad, actually:
>
> $ ghc --make hello
> [1 of 2] Compiling Prelude          ( Prelude.hs, Prelude.o )
> [2 of 2] Compiling Main             ( hello.hs, hello.o )
>
> hello.hs:1:8: Not in scope: `putStr'
>
> You can pretty clearly see what happened there.

When something goes wrong with a basic system
component like the Prelude, the natural
reaction of most people is panic. I've been getting file
system corruption lately on a removable hard disk - could
it be that? Did I cause this when I moved around some
system directories the other day? Are my different copies
of GHC getting mixed up with each other's files?

It's hard to overestimate how much a soothing message
from GHC is appreciated in that kind of situation.

Thanks,
Yitz
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: I accidentally the Prelude

2010-03-03 Thread Simon Marlow

On 03/03/2010 12:37, Yitzchak Gale wrote:

Jeremy Shaw wrote:

I would still vote for that error in the 'worst ghc error message
contest'...


I wrote:

Can't we add something like "(Is there more than one
Prelude in your path?)" to the message for Prelude?


Simon Marlow wrote:

So I could add a warning ("Warning: this Prelude module is shadowing the
real Prelude", or something), but then we'd need a new flag to turn off the
warning if shadowing the Prelude is what you're really trying to do, and
that sounds like an awful lot of bother to fix a very rare corner case.  Or
can anyone think of a better way to handle this?


I was suggesting that whenever the Prelude fails to load,
the error message should contain that hint.


hmm, I'll think about that. Is it not enough to see a compilation error 
pointing to the file Prelude.hs?



We'd also like to help rescue people who get weird behavior
when, unbeknownst to them, the wrong Prelude loads
successfully. But I understand your point that this second case
is trickier and may not be worth the effort.


it's probably not that bad, actually:

$ ghc --make hello
[1 of 2] Compiling Prelude  ( Prelude.hs, Prelude.o )
[2 of 2] Compiling Main ( hello.hs, hello.o )

hello.hs:1:8: Not in scope: `putStr'


You can pretty clearly see what happened there.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: I accidentally the Prelude

2010-03-03 Thread Yitzchak Gale
Jeremy Shaw wrote:
>>> I would still vote for that error in the 'worst ghc error message
>>> contest'...

I wrote:
>> Can't we add something like "(Is there more than one
>> Prelude in your path?)" to the message for Prelude?

Simon Marlow wrote:
> So I could add a warning ("Warning: this Prelude module is shadowing the
> real Prelude", or something), but then we'd need a new flag to turn off the
> warning if shadowing the Prelude is what you're really trying to do, and
> that sounds like an awful lot of bother to fix a very rare corner case.  Or
> can anyone think of a better way to handle this?

I was suggesting that whenever the Prelude fails to load,
the error message should contain that hint.

We'd also like to help rescue people who get weird behavior
when, unbeknownst to them, the wrong Prelude loads
successfully. But I understand your point that this second case
is trickier and may not be worth the effort.

Thanks,
Yitz
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: I accidentally the Prelude

2010-03-03 Thread Simon Marlow

On 02/03/2010 17:45, Yitzchak Gale wrote:

Jeremy Shaw wrote:

I would still vote for that error in the 'worst ghc error message
contest'...


Simon Marlow wrote:

Oh, the problem here is that... when we got around
to trying to import it we found that it was not "loaded".
Perhaps the implicit import of Prelude should be...
What you wanted to do above was "ghc --make Setup -i"...
And if we fix the dependency thing, you'll still need to do that,
because otherwise...


Simon,

Thank you for your incessant focus on making GHC excellent
in every case!

Even so, Prelude does seem to be a special case here,
and in that special case the error message really is bad.
It even confused Josef.

Can't we add something like "(Is there more than one
Prelude in your path?)" to the message for Prelude?
Just in case somehow, somewhere, this does happen
to someone again?


After making the fix I mentioned previously, the result is now this:

  libraries/base$ ghc --make Setup

  Prelude.hs:38:2: lexical error at character 'i'

which is reasonable, because Setup.hs imports Prelude (implicitly), and 
Prelude.hs was found in the current directory.  Prelude.hs has some CPP 
directives which result in the compilation error.


So I could add a warning ("Warning: this Prelude module is shadowing the 
real Prelude", or something), but then we'd need a new flag to turn off 
the warning if shadowing the Prelude is what you're really trying to do, 
and that sounds like an awful lot of bother to fix a very rare corner 
case.  Or can anyone think of a better way to handle this?


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users