Installation

2011-04-20 Thread Luca Ciciriello

Hi All.I'm using GHC with MacOS X 10.6.7 (Xcode4). I've installed GHC 7.0.3 and 
the HackageDB package hsgsom. Then, for my motivation, I've uninstalled GHC.To 
remove GHC I've used the uninstaller tool and I've manually removed the folder 
/Library/Frameworks/GHC.framework. I've also manually removed the folder 
/Users/MyUser/Library/Haskell and the folder /Users/MyUser/.cabal
Now I've installed GHC again, but when I try to install the package hsgsom 
cabal tells to me that the package is already installed and I have to use the 
--reinstall flag. So, where the information of the installed packages are 
stored on my system? How can I remove all Haskell dependencies from my system 
in order to start with a clean installation?
Thanks in advance for any answer.
Luca. ___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC/LLDB integration

2011-04-20 Thread Edward Z. Yang
Hello William,

You can find the state of the art (which isn't very advanced :-)
in debugging GHC compiled code with GDB here:

http://hackage.haskell.org/trac/ghc/wiki/Debugging/CompiledCode

Maybe others can give more specific advice.

Cheers,
Edward

Excerpts from William Knop's message of Mon Apr 18 13:50:03 -0400 2011:
 Hello all,
 I've been using LLDB for a few weeks now, initially acquainting myself
 with its python bindings. It occurred to me early on that they might
 integrate into GHC's testsuite well, so I began writing a driver. The
 idea was to encapsulate the launched haskell processes in LLDB and
 generate more useful debugging information for failed tests (I'd
 previously been hunting down a few spurious segfaults). However, LLDB
 is quite immature and currently lacking such capabilities as
 generating core files, among other things.
 
 But while searching for core file generation, I ended up discovering
 that it is to eventually be implemented as a native plugin. It turns
 out that the plugin system allows for a lot of extensibility,
 including language and ABI extension. So I started digging into that
 and just recently began working on adding a GHRuntime plugin which
 should allow for demangling of symbols (easy), analysis and
 description of info tables and call graphs (hard), etc.
 
 So before I get too far into it, and because I am not a GHC guru, I'd
 like to gauge it's ultimate usefulness amongst the community. Given
 that haskell code goes through several stages of transformation, can
 more useful information be derived from a debugged executable? Or can
 more useful debug information be emitted by GHC if it can be
 interpreted by a purpose-made debugger plugin? If so, what information
 and functionality would be desirable? Ideas and comments are most
 welcome.
 
 Will
 

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


Re: GHC/LLDB integration

2011-04-20 Thread Simon Marlow

On 18/04/2011 18:50, William Knop wrote:

Hello all,
I've been using LLDB for a few weeks now, initially acquainting myself
with its python bindings. It occurred to me early on that they might
integrate into GHC's testsuite well, so I began writing a driver. The
idea was to encapsulate the launched haskell processes in LLDB and
generate more useful debugging information for failed tests (I'd
previously been hunting down a few spurious segfaults). However, LLDB
is quite immature and currently lacking such capabilities as
generating core files, among other things.

But while searching for core file generation, I ended up discovering
that it is to eventually be implemented as a native plugin. It turns
out that the plugin system allows for a lot of extensibility,
including language and ABI extension. So I started digging into that
and just recently began working on adding a GHRuntime plugin which
should allow for demangling of symbols (easy), analysis and
description of info tables and call graphs (hard), etc.

So before I get too far into it, and because I am not a GHC guru, I'd
like to gauge it's ultimate usefulness amongst the community. Given
that haskell code goes through several stages of transformation, can
more useful information be derived from a debugged executable? Or can
more useful debug information be emitted by GHC if it can be
interpreted by a purpose-made debugger plugin? If so, what information
and functionality would be desirable? Ideas and comments are most
welcome.


Sounds interesting, though I know nothing about LLDB.  It would be nice 
to have a little help from the debugger for things like:


 - displaying the stack in a nicer way
 - displaying heap objects
 - searching the heap
 - displaying runtime state: what threads exist and what state
   they're in, summary of various RTS data structures, etc.

For some of these I have C functions in the RTS that I can call from 
gdb.  e.g. there's findPtr() that searches the heap for occurrences of a 
particular pointer (useful for debugging leaks when the higher level 
tools don't give you enough information).


Cheers,
Simon

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


Re: Installation

2011-04-20 Thread David Peixotto
Perhaps the /Users/MyUser/.ghc folder is causing your problem?

On Apr 20, 2011, at 2:33 AM, Luca Ciciriello wrote:

 Hi All.
 I'm using GHC with MacOS X 10.6.7 (Xcode4). I've installed GHC 7.0.3 and the 
 HackageDB package hsgsom. Then, for my motivation, I've uninstalled GHC.
 To remove GHC I've used the uninstaller tool and I've manually removed the 
 folder /Library/Frameworks/GHC.framework. I've also manually removed the 
 folder /Users/MyUser/Library/Haskell and the folder /Users/MyUser/.cabal
 
 Now I've installed GHC again, but when I try to install the package hsgsom 
 cabal tells to me that the package is already installed and I have to use the 
 --reinstall flag. So, where the information of the installed packages are 
 stored on my system? How can I remove all Haskell dependencies from my system 
 in order to start with a clean installation?
 
 Thanks in advance for any answer.
 
 Luca.
 ___
 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: Installation

2011-04-20 Thread Luca Ciciriello


 Yes, that is the folder to delete to start with a clean installation.
 
Thanks.
 
Luca.


Subject: Re: Installation
From: d...@rice.edu
Date: Wed, 20 Apr 2011 07:36:16 -0500
CC: glasgow-haskell-users@haskell.org
To: luca_cicirie...@hotmail.com


Perhaps the /Users/MyUser/.ghc folder is causing your problem?




On Apr 20, 2011, at 2:33 AM, Luca Ciciriello wrote:

Hi All.
I'm using GHC with MacOS X 10.6.7 (Xcode4). I've installed GHC 7.0.3 and the 
HackageDB package hsgsom. Then, for my motivation, I've uninstalled GHC.
To remove GHC I've used the uninstaller tool and I've manually removed the 
folder /Library/Frameworks/GHC.framework. I've also manually removed the folder 
/Users/MyUser/Library/Haskell and the folder /Users/MyUser/.cabal


Now I've installed GHC again, but when I try to install the package hsgsom 
cabal tells to me that the package is already installed and I have to use the 
--reinstall flag. So, where the information of the installed packages are 
stored on my system? How can I remove all Haskell dependencies from my system 
in order to start with a clean installation?


Thanks in advance for any answer.


Luca.___
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


Type-level operators

2011-04-20 Thread Stefan Holdermans
Simon,

Regarding the note you attached to the Trac ticket on the pretty-printing of 
kind ascriptions (http://hackage.haskell.org/trac/ghc/ticket/5141#comment:2):

 Note, though, that it's likely that we're considering making operators
 like '*' into type ''constructors'' rather that type ''variables'.  This
 is inconsitent with terms, but is jolly convenient:
 {{{
 data a + b = Left a | Right b
 }}}
 Of course there'll be a flag.  But let us know if you think that having
 operators be type variables is very useful.  (I tend to think it's more
 confusing than useful.)

I myself am perfectly alright with being forced to write

{{{
data a :+: b = Left a | Right b
}}}

Although I don't have a *convincing* example of the usefulness of operators as 
type variables, I like the idea of consistency with the term level: IMO it 
keeps things predictable.

And even as it may not qualify as convincing, I do remember having written code 
similar to

{{{
data (f :+: g) a = Inl (f a) | Inr (g a)
data (f :*: g) a = f a :*: g a

class FunctorOp (() :: (* - *) - (* - *) - (* - *)) where ...
instance FunctorOp (:+:) where ...
instance FunctorOp (:*:) where ...

class FunctorOp () = CommOp () where comm :: f  g - g  f
instance CommOp (:+:) where ...
instance CommOp (:*:) where ...

f :: (CommOp (), Functor f, Functor g) - f  g - ...
f ... = ...
}}}

All this, of course, just to put in my tuppence worth.

Cheers,

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


Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Daniel Fischer
Investigating the appearance of NaN in criterion's output, I found that 
NaNs were frequently introduced into the resample vectors when the 
resamples were sorted.

Further investigation of the sorting code in vector-algorithms revealed no 
bugs there, and if the runtime was forced to keep a keen eye on the 
indices, by replacing unsafeRead/Write/Swap with their bounds-checked 
counterparts or by 'trace'ing enough of their uses, the NaNs did not 
appear.

I could not reproduce the behaviour with ghc-7.0.1 (using exactly the same 
versions of the involved libraries), ghc-7.0.2 (different criterion 
release, the other libraries identical) or unoptimised compilation with 
7.0.3 (no NaNs encountered in some 100+ testruns with varying input).

So, is it possible that some change in ghc-7.0.3 vs. the previous versions 
caused a bad interaction between ghc-optimisations and vector fusion 
resulting in bad vector reads/writes?

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Roman Leshchinskiy
Daniel Fischer wrote:

 Further investigation of the sorting code in vector-algorithms revealed
 no bugs there, and if the runtime was forced to keep a keen eye on the
 indices, by replacing unsafeRead/Write/Swap with their bounds-checked
 counterparts or by 'trace'ing enough of their uses, the NaNs did not
 appear.

Did you replace them in vector-algorithms or in vector itself?

 So, is it possible that some change in ghc-7.0.3 vs. the previous
 versions caused a bad interaction between ghc-optimisations and vector
 fusion resulting in bad vector reads/writes?

Am I right in assuming that this happens in code which uses only mutable
vectors? Fusion only works for immutable ones so it shouldn't really
affect things here.

Have you tried playing around with code generation flags like -msse2?

In any case, I would try to take a look at this if you tell me how to
reproduce.

Roman




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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Ian Lynagh
On Wed, Apr 20, 2011 at 05:02:50PM +0200, Daniel Fischer wrote:
 
 So, is it possible that some change in ghc-7.0.3 vs. the previous versions 

Very little changed between 7.0.2 and 7.0.3. The only thing that jumps
out to me as possibly being relevant is:

diff -ur 7.0.2/ghc-7.0.2/compiler/nativeGen/X86/Instr.hs 
7.0.3/ghc-7.0.3/compiler/nativeGen/X86/Instr.hs
--- 7.0.2/ghc-7.0.2/compiler/nativeGen/X86/Instr.hs 2011-02-28 
18:10:06.0 +
+++ 7.0.3/ghc-7.0.3/compiler/nativeGen/X86/Instr.hs 2011-03-26 
18:10:04.0 +
@@ -734,6 +734,7 @@
  where p insn r = case insn of
 CALL _ _ - GFREE : insn : r
 JMP _- GFREE : insn : r
+JXX_GBL _ _ - GFREE : insn : r
 _- insn : r


Thanks
Ian


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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Daniel Fischer
On Wednesday 20 April 2011 19:11:07, Roman Leshchinskiy wrote:
 Daniel Fischer wrote:
  Further investigation of the sorting code in vector-algorithms
  revealed no bugs there, and if the runtime was forced to keep a keen
  eye on the indices, by replacing unsafeRead/Write/Swap with their
  bounds-checked counterparts or by 'trace'ing enough of their uses,
  the NaNs did not appear.
 
 Did you replace them in vector-algorithms or in vector itself?
 

vector-algorithms only.

  So, is it possible that some change in ghc-7.0.3 vs. the previous
  versions caused a bad interaction between ghc-optimisations and vector
  fusion resulting in bad vector reads/writes?
 
 Am I right in assuming that this happens in code which uses only mutable
 vectors?

Yes, the sorting uses mutable vectors, in this case unboxed Double vectors.

 Fusion only works for immutable ones so it shouldn't really
 affect things here.

Ah, didn't know that. Another suspect gone.

 
 Have you tried playing around with code generation flags like -msse2?

No, not yet. So far only -O2 (with -fspec-constr-count=5 in the presence of 
many trace calls) and -O0.

 
 In any case, I would try to take a look at this if you tell me how to
 reproduce.

I'll prepare a bundle, I'm afraid it won't be small, though. And it might 
be architecture dependent, so I can't guarantee that you will be able to 
reproduce it. But Bryan said on IRC yesterday that others have reported 
similar issues with criterion output, so it may well be cross-platform 
reproducible.

Cheers,
Daniel

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Daniel Fischer
On Wednesday 20 April 2011 20:25:34, Bryan O'Sullivan wrote:
 On Wed, Apr 20, 2011 at 10:44 AM, Daniel Fischer 
 
 daniel.is.fisc...@googlemail.com wrote:
  I'll prepare a bundle, I'm afraid it won't be small, though. And it
  might be architecture dependent, so I can't guarantee that you will
  be able to reproduce it. But Bryan said on IRC yesterday that others
  have reported similar issues with criterion output, so it may well be
  cross-platform reproducible.
 
 Daniel, are you sure this is down to a 7.0.2/7.0.3 difference, and not
 perhaps due to just a bug in criterion itself?

I'm sure it's not criterion, because after I've found that NaNs were 
introduced to the resamples vectors during sorting (check the entire 
vectors for NaNs before and aftersorting, tracing the count; before: 0, 
afterwards often quite a number, sometimes close to 10%), the further tests 
didn't involve criterion anymore. criterion is simply the most obvious 
place to see the NaNs show up (with 5-10% NaNs among the resamples, it 
won't take too long to see one pop up).

It could be a bug in statistics, but I'm pretty sure this one's not due to 
statistics either, since fiddling with vector-algorithms made the NaNs 
disappear - btw., Bryan, using the heap sort instead of introsort, I 
haven't found any NaNs in my tests, so temporarily switching the algorithm 
might cure the symptoms.

Dan Doel and I spent not too little time scrutinising the vector-algorithms 
code without finding an issue. Also, replacing the unsafe access with 
bounds-checked access (apparently) eliminated the NaNs, and 7.0.1 and 7.0.2 
didn't produce any in my tests, yet more points to believe that it's none 
of these packages producing the behaviour, but rather something that 
changed between 7.0.2 and 7.0.3 -- however, so far in this matter my 
guesses as to what's responsible have been wrong, so I wouldn't be 
surprised if it's something entirely different.

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Dan Doel
On Wed, Apr 20, 2011 at 3:01 PM, Daniel Fischer
daniel.is.fisc...@googlemail.com wrote:
 I'm sure it's not criterion, because after I've found that NaNs were
 introduced to the resamples vectors during sorting (check the entire
 vectors for NaNs before and aftersorting, tracing the count; before: 0,
 afterwards often quite a number, sometimes close to 10%), the further tests
 didn't involve criterion anymore. criterion is simply the most obvious
 place to see the NaNs show up (with 5-10% NaNs among the resamples, it
 won't take too long to see one pop up).

 It could be a bug in statistics, but I'm pretty sure this one's not due to
 statistics either, since fiddling with vector-algorithms made the NaNs
 disappear - btw., Bryan, using the heap sort instead of introsort, I
 haven't found any NaNs in my tests, so temporarily switching the algorithm
 might cure the symptoms.

It's not a statistics bug. I'm reproducing it here using just vector-algorithms.

Fill a vector of size N with [N..1], and (intro) sort it, and you get
NaNs. But only with -O or above. Without optimization it doesn't
happen (and nothing seems to be reading/writing out of bounds, as I
compiled vector with UnsafeChecks earlier and it didn't complain).

Filling the vector with [1..N] also doesn't trigger the NaNs. [0,0..0]
and [0,0..1] trigger it.

I don't know what's going on yet. I have trouble believing it's a bug
in vector-algorithms code, though, as I don't think I've written any
RULEs (just INLINEs), and that's the one thing that comes to mind in
library code that could cause a difference between -O0 and -O. So I'd
tentatively suggest it's a vector, base or compiler bug.

The above testing is on 64-bit windows running a 32-bit copy of GHC,
for reference.

My ability to investigate this will be a bit limited for the near
future. If someone definitively tracks it down to bugs in my code,
though, let me know, and I'll try and push a new release up on
hackage.

-- Dan

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


Re: Broken ghc-7.0.3/vector combination?

2011-04-20 Thread Daniel Fischer
On Wednesday 20 April 2011 21:55:51, Dan Doel wrote:
 
 It's not a statistics bug. I'm reproducing it here using just
 vector-algorithms.

Yep. Attached a simple testcasewhich reproduces it and uses only vector and 
vector-algorithms.

 
 Fill a vector of size N with [N..1], and (intro) sort it, and you get
 NaNs. But only with -O or above.

However, for me the NaNs disappear with the -msse2 option.

 Without optimization it doesn't
 happen (and nothing seems to be reading/writing out of bounds, as I
 compiled vector with UnsafeChecks earlier and it didn't complain).

Nor does it happen here with 7.0.2 or 7.0.1.

 
 Filling the vector with [1..N] also doesn't trigger the NaNs. [0,0..0]
 and [0,0..1] trigger it.
 
 I don't know what's going on yet. I have trouble believing it's a bug
 in vector-algorithms code, though, as I don't think I've written any
 RULEs (just INLINEs), and that's the one thing that comes to mind in
 library code that could cause a difference between -O0 and -O. So I'd
 tentatively suggest it's a vector, base or compiler bug.
 
 The above testing is on 64-bit windows running a 32-bit copy of GHC,
 for reference.

32-bit linux here

 
 My ability to investigate this will be a bit limited for the near
 future. If someone definitively tracks it down to bugs in my code,
 though, let me know, and I'll try and push a new release up on
 hackage.
 
 -- Dan
{-# LANGUAGE BangPatterns #-}
module Main where

import qualified Data.Vector.Unboxed.Mutable as MU
import Data.Vector.Unboxed.Mutable (IOVector, unsafeRead, unsafeWrite, new)
import qualified Data.Vector.Algorithms.Intro as I

import Control.Monad (when)
import System.Environment (getArgs)

countNaNs :: IOVector Double - IO Int
countNaNs a = go 0 0
  where
len = MU.length a
go !ct i
| i  len = do
x - unsafeRead a i
go (if isNaN x then ct+1 else ct) (i+1)
| otherwise = return ct

sample :: Int - IO (IOVector Double)
sample k = do
a - new k
let foo :: Double - Double
foo x = 1.0 + sin x / x
fill i x
| i  k = do
unsafeWrite a i (foo x)
fill (i+1) (x+1.0)
| otherwise = return a
fill 0 (fromIntegral k * 10)

main :: IO ()
main = do
args - getArgs
let k = case args of
  (arg:_) - read arg
  _   - 1
a - sample k
b - countNaNs a
when (b /= 0) (putStrLn $ Before sorting:  ++ show b ++  NaNs.)
I.sort a
c - countNaNs a
when (c /= 0) (putStrLn $ After sorting:  ++ show c ++  NaNs.)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users