Re: love for hpc?

2013-11-07 Thread Johan Tibell
Aside: cabal supports hpc and puts the various files (e.g. .tix) in
separate directories to avoid problems like these.


On Thu, Nov 7, 2013 at 8:55 AM, Roman Cheplyaka r...@ro-che.info wrote:

 So Evan's prediction was accurate ;-)

 * Carter Schonwald carter.schonw...@gmail.com [2013-11-07 00:29:24-0500]
  Evan,
 
  if  you want to get involved in working on HPC, go for it! theres many
 many
  pieces of ghc that need more proactive ownership.
 
  i should probably use HPC a bit as i start getting my numerical libs out,
  and i'm sure future me will appreciate current you working on making it
  better
 
  -Carter
 
 
  On Thu, Nov 7, 2013 at 12:03 AM, Evan Laforge qdun...@gmail.com wrote:
 
   Is anyone out there using HPC?  It seems like it was gotten into a
   more or less working if not ideal state, and then abandoned.
  
   Things I've noticed lately:
  
   The GHC runtime just quits on the spot if there's already a tix file.
   This bit me when I was parallelizing tests.  It's also completely
   unsafe when run concurrently, mostly it just overwrites the file,
   sometimes it quits.  Sure to cause headaches for someone trying to
   parallelize tests.
  
   You can't change the name of the output tix file, so I worked around
   by hardlinking the binary to a bunch of new ones, and then doing 'hpc
   sum' on the results.
  
   The hpc command is super slow.  It might have to do with it doing its
   parsing with Prelude's 'read', and it certainly doesn't help the error
   msgs.
  
   And the whole thing is generally minimally documented.
  
   I can already predict the answer will be yes, HPC could use some
   love, roll up your sleeves and welcome!  It does look like it could
   be improved a lot with just a bit of effort, but that would be a yak
   too far for me, at the moment.  I'm presently just curious if anyone
   else out there is using it, and if they feel like it could do with a
   bit of polishing.
   ___
   Glasgow-haskell-users mailing list
   Glasgow-haskell-users@haskell.org
   http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
  

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


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


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


Re: love for hpc?

2013-11-07 Thread Erik Hesselink
I use HPC. It's really powerful in combination with tests, to see how
much of your code is covered. But I have also run into some of the
problems you mention, mostly to do with tix files.

Erik

On Thu, Nov 7, 2013 at 6:03 AM, Evan Laforge qdun...@gmail.com wrote:
 Is anyone out there using HPC?  It seems like it was gotten into a
 more or less working if not ideal state, and then abandoned.

 Things I've noticed lately:

 The GHC runtime just quits on the spot if there's already a tix file.
 This bit me when I was parallelizing tests.  It's also completely
 unsafe when run concurrently, mostly it just overwrites the file,
 sometimes it quits.  Sure to cause headaches for someone trying to
 parallelize tests.

 You can't change the name of the output tix file, so I worked around
 by hardlinking the binary to a bunch of new ones, and then doing 'hpc
 sum' on the results.

 The hpc command is super slow.  It might have to do with it doing its
 parsing with Prelude's 'read', and it certainly doesn't help the error
 msgs.

 And the whole thing is generally minimally documented.

 I can already predict the answer will be yes, HPC could use some
 love, roll up your sleeves and welcome!  It does look like it could
 be improved a lot with just a bit of effort, but that would be a yak
 too far for me, at the moment.  I'm presently just curious if anyone
 else out there is using it, and if they feel like it could do with a
 bit of polishing.
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHC error message on type mismatch

2013-11-07 Thread Daniel Trstenjak

Hello,

I don't know if I'm the only one struggeling with this GHC error message
on type mismatches or it's because I'm not a full time Haskeller, or
because I'm not a native english speaker.

Couldn't match type `A' with `B´
Expected type: B
  Actual type: A


My problem is with 'Expected' and 'Actual', that I'm often unsure if
the compiler is expecting something or if I'm the expecting one
and the same goes for actual.

I know that the compiler is the expecting one and that I'm given the
actual thing, but it's quite often that I'm looking at this error
and have to repeat this reasoning.

It's strange, because normaly I can memorize such things quite good,
but this one bothers me.

Perhaps it would be easier for myself if 'Actual type' would be called
e.g. 'Given type', I don't know, that just one of the two has a less
generic meaning.


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


Re: GHC error message on type mismatch

2013-11-07 Thread David Luposchainsky
On 2013-11-07 12:52, Daniel Trstenjak wrote:
 My problem is with 'Expected' and 'Actual', that I'm often unsure if
 the compiler is expecting something or if I'm the expecting one
 and the same goes for actual.

Funny you mention it; I think I just got too used to the fact that every
time I see this error I have to take a step back to remember what it
means exactly. Renaming it to given or provided would really help.

+1

David

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


Re: GHC error message on type mismatch

2013-11-07 Thread David Fox
It *is* sometimes difficult to remember that my expectations and I are not
part of this equation - it might be a better prompt to say something like

   type mismatch between function parameter and supplied value:
  function parameter type: A
  supplied value type: B


On Thu, Nov 7, 2013 at 6:02 AM, Simon Peyton-Jones simo...@microsoft.comwrote:

 The motivation is this. Consider

 f True

 where f :: Int - Char

 Then
   f *expects* an argument of type Int
   but the *actual* argument has type Bool

 Does that help?

 Simon

 | -Original Message-
 | From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
 | boun...@haskell.org] On Behalf Of David Luposchainsky
 | Sent: 07 November 2013 12:23
 | To: Daniel Trstenjak; glasgow-haskell-users@haskell.org
 | Subject: Re: GHC error message on type mismatch
 |
 | On 2013-11-07 12:52, Daniel Trstenjak wrote:
 |  My problem is with 'Expected' and 'Actual', that I'm often unsure if
 |  the compiler is expecting something or if I'm the expecting one
 |  and the same goes for actual.
 |
 | Funny you mention it; I think I just got too used to the fact that every
 | time I see this error I have to take a step back to remember what it
 | means exactly. Renaming it to given or provided would really help.
 |
 | +1
 |
 | David
 |
 | ___
 | Glasgow-haskell-users mailing list
 | Glasgow-haskell-users@haskell.org
 | http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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


RE: match_co: needs more cases

2013-11-07 Thread crockeea
I got this error with a small example, so I thought I'd post it for you. I
could only get it to work when split over two files.


Main.hs:
import qualified Data.Vector.Unboxed as U
import Helper

main = do
let iters = 100
dim = 221184
y = U.replicate dim 0 :: U.Vector (ZqW M)
let ans = iterate (f y) y !! iters
putStr $ (show $ U.foldl1' (+) ans)


Helper.hs
{-# LANGUAGE FlexibleContexts, StandaloneDeriving,
GeneralizedNewtypeDeriving, MultiParamTypeClasses #-}
module VectorTestHelper (ZqW,f,M) where

import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Generic as V
import Data.Vector.Generic.Mutable   as M

f :: (Num r, V.Vector v r) = v r - v r - v r
{-# SPECIALIZE f :: (Num (ZqW m Int)) = U.Vector (ZqW m Int) - U.Vector
(ZqW m Int) - U.Vector (ZqW m Int) #-}
f x y = V.zipWith (+) x y


newtype ZqW p i = T i deriving (U.Unbox, Show)
deriving instance (U.Unbox i) = V.Vector U.Vector (ZqW p i)
deriving instance (U.Unbox i) = MVector U.MVector (ZqW p i)

class Foo a b

data M
instance Foo M Int

instance (Foo p i, Integral i) = Num (ZqW p i) where
(T a) + (T b) = T $ (a+b)

fromInteger x = T $ fromInteger x


It's possible I'm abusing SPECIALIZE here, but I'm trying to get Unboxed
vector specialization, even though I have a phantom type. (In practice, the
phantom will represent a modulus and will be used in the Num instance).

When compiling with GHC 7.6.2 and -O2, I get a dozen or so match_co: needs
more cases warnings. Indeed, based on the runtime, it appears that
specialization is not happening. How to actually make this work is a whole
different question...



--
View this message in context: 
http://haskell.1045720.n5.nabble.com/match-co-needs-more-cases-tp5730855p5739541.html
Sent from the Haskell - Glasgow-haskell-users mailing list archive at 
Nabble.com.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: match_co: needs more cases

2013-11-07 Thread Evan Laforge
On Thu, Nov 7, 2013 at 11:11 AM, crockeea ecrocke...@gmail.com wrote:
 I got this error with a small example, so I thought I'd post it for you. I
 could only get it to work when split over two files.

Mine is similar, sorry I've been lazy about getting a small
reproduction, I assumed it wasn't too important.

I have a generic library that uses Data.Vector.Generic, along with a
bunch of SPECIALIZE and INLINEABLE for a particular monomorphic
Unboxed use.  I don't know about the INLINEABLE, but the SPECIALIZE
does wonders for performance, otherwise it doesn't notice that the
operation can be unboxed.

So it's a bit worrisome to me if the SPECIALIZEs aren't firing.  I did
profiling before and they made my vector operations fall off of the
expensive list, but that was before upgrading ghc and getting the new
error msgs.

Would it be useful for me to boil down my example too, or is this one
enough to work on?  Mine is simpler in that it specializes to a
monomorphic Storable.Vector Double.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: match_co: needs more cases

2013-11-07 Thread Carter Schonwald
specialize only fires on functions that have type class constraints / are
part of a type class.  Furthermore, the function needs to be marked
INLINEABLE or INLINE for specialization to work (unless the specialize
pragma was written in the defining module)

not sure if that helps,

cheers
-Carter


On Thu, Nov 7, 2013 at 7:17 PM, Evan Laforge qdun...@gmail.com wrote:

 On Thu, Nov 7, 2013 at 11:11 AM, crockeea ecrocke...@gmail.com wrote:
  I got this error with a small example, so I thought I'd post it for you.
 I
  could only get it to work when split over two files.

 Mine is similar, sorry I've been lazy about getting a small
 reproduction, I assumed it wasn't too important.

 I have a generic library that uses Data.Vector.Generic, along with a
 bunch of SPECIALIZE and INLINEABLE for a particular monomorphic
 Unboxed use.  I don't know about the INLINEABLE, but the SPECIALIZE
 does wonders for performance, otherwise it doesn't notice that the
 operation can be unboxed.

 So it's a bit worrisome to me if the SPECIALIZEs aren't firing.  I did
 profiling before and they made my vector operations fall off of the
 expensive list, but that was before upgrading ghc and getting the new
 error msgs.

 Would it be useful for me to boil down my example too, or is this one
 enough to work on?  Mine is simpler in that it specializes to a
 monomorphic Storable.Vector Double.
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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


Re: match_co: needs more cases

2013-11-07 Thread Evan Laforge
On Thu, Nov 7, 2013 at 4:20 PM, Carter Schonwald
carter.schonw...@gmail.com wrote:
 specialize only fires on functions that have type class constraints / are
 part of a type class.  Furthermore, the function needs to be marked
 INLINEABLE or INLINE for specialization to work (unless the specialize
 pragma was written in the defining module)

Right, and I added it because I wanted to get rid of both the
Vector.Generic typeclass, and the Unboxed typeclass, and it worked.  I
guess that's why I added INLINEABLEs too, I probably read about it in
the documentation and then forgot.  But if crockeea is right and it's
no longer happening, that would be unfortunate.

I wonder if you could write a kind of query language for core, to ask
things like are the arguments to this function unboxed? or how many
list constructors are called here (e.g. to check for fusion).

 not sure if that helps,

It does, thanks!
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC error message on type mismatch

2013-11-07 Thread Daniel Trstenjak

Hi Simon,

On Thu, Nov 07, 2013 at 02:02:06PM +, Simon Peyton-Jones wrote:
 The motivation is this. Consider
 
   f True
 
 where f :: Int - Char
 
 Then 
   f *expects* an argument of type Int
   but the *actual* argument has type Bool
 
 Does that help?

If you would switch the meaning of 'Expected' and 'Actual', than it
still could make perfectly sense and my brain seems to tend to this
switched meaning.

I think my main issue is the word 'Actual'. I seem to associate
something more authoritative with this word and not just a wrongly given
type by the user, and on the other side 'Expected' doesn't feel authoritative
enough.

Yes, I think the combination of the words 'Expected' and 'Actual' is
irritating me and that I'm perceiving 'Actual' as the more authoritative one.


Perhaps:

Couldn't match type `A' with `B´
Real  type: B
Given type: A


Or instead of 'Given', like others have suggested: 'Provided' or 'Supplied'.


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


Re: GHC error message on type mismatch

2013-11-07 Thread Carter Schonwald
i'm not sure how change the words to synonyms helps communicate the exact
same thing better, :)

That said, once you start digging into really really fancy types, you'll
certainly discover examples where the error messages are confusing and need
some care to better communicate what is indeed the error.

Point being: as you get into trying out really really fancy types, please
feel welcome to  share examples where the resulting error messages seem
lacking / down right confusing. (though asking for help on the cafe list or
#haskell on irc first is probably the first place to go, of course)


On Thu, Nov 7, 2013 at 11:54 PM, Daniel Trstenjak 
daniel.trsten...@gmail.com wrote:


 Hi Simon,

 On Thu, Nov 07, 2013 at 02:02:06PM +, Simon Peyton-Jones wrote:
  The motivation is this. Consider
 
f True
 
  where f :: Int - Char
 
  Then
f *expects* an argument of type Int
but the *actual* argument has type Bool
 
  Does that help?

 If you would switch the meaning of 'Expected' and 'Actual', than it
 still could make perfectly sense and my brain seems to tend to this
 switched meaning.

 I think my main issue is the word 'Actual'. I seem to associate
 something more authoritative with this word and not just a wrongly given
 type by the user, and on the other side 'Expected' doesn't feel
 authoritative
 enough.

 Yes, I think the combination of the words 'Expected' and 'Actual' is
 irritating me and that I'm perceiving 'Actual' as the more authoritative
 one.


 Perhaps:

 Couldn't match type `A' with `B´
 Real  type: B
 Given type: A


 Or instead of 'Given', like others have suggested: 'Provided' or
 'Supplied'.


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

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


Re: GHC error message on type mismatch

2013-11-07 Thread Dan Frumin

Hi everyone 

 On 07 Nov 2013, at 23:54, Daniel Trstenjak daniel.trsten...@gmail.com wrote:
 
 
 Hi Simon,
 
 On Thu, Nov 07, 2013 at 02:02:06PM +, Simon Peyton-Jones wrote:
 The motivation is this. Consider
 
f True
 
 where f :: Int - Char
 
 Then 
  f *expects* an argument of type Int
  but the *actual* argument has type Bool
 
 Does that help?
 
 If you would switch the meaning of 'Expected' and 'Actual', than it
 still could make perfectly sense and my brain seems to tend to this
 switched meaning.
 

Yeah I can see how that may happen. 

f's argument type is *actually* an Int, but it was used in a way that caller 
*expects* it to have a type Bool

 I think my main issue is the word 'Actual'. I seem to associate
 something more authoritative with this word and not just a wrongly given
 type by the user, and on the other side 'Expected' doesn't feel authoritative
 enough.
 
 Yes, I think the combination of the words 'Expected' and 'Actual' is
 irritating me and that I'm perceiving 'Actual' as the more authoritative one.
 
 
 Perhaps:
 
 Couldn't match type `A' with `B´
Real  type: B
Given type: A
 
 
 Or instead of 'Given', like others have suggested: 'Provided' or 'Supplied'.
 
 
 Greetings,
 Daniel
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC error message on type mismatch

2013-11-07 Thread Roman Cheplyaka
* Daniel Trstenjak daniel.trsten...@gmail.com [2013-11-08 05:54:49+0100]
 Perhaps:
 
 Couldn't match type `A' with `B´
 Real  type: B
 Given type: A
 
 
 Or instead of 'Given', like others have suggested: 'Provided' or 'Supplied'.

So far in this thread I haven't seen any suggestions better than status
quo.

E.g.:

  Prelude (undefined :: Int - Bool) (undefined :: Bool)

  interactive:2:29:
  Couldn't match expected type `Int' with actual type `Bool'
  In the first argument of `undefined :: Int - Bool', namely
`(undefined :: Bool)'
  In the expression: (undefined :: Int - Bool) (undefined :: Bool)
  In an equation for `it':
  it = (undefined :: Int - Bool) (undefined :: Bool)

This one is quite clear — the compiler expected an argument of type Int,
but it was of type Bool.

Now replace this with Real and Given. Well, Bool for the function
argument is both Real and Given (I gave it this type, and it became its
real type). And calling Int either Real or Given doesn't make any sense.

Roman


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