Re: [Haskell-cafe] Looking for portable Haskell or Haskell like language

2013-04-27 Thread Daniel Fischer
On Saturday 27 April 2013, 19:18:35, Andrew Cowie wrote:
 On Fri, 2013-04-26 at 21:21 -0800, Christopher Howard wrote:
  Hi. I've got this work situation where I've got to do all my work on
  /ancient/ RHEL5 systems, with funky software configurations, and no root
  privileges. I wanted to install GHC in my local account, but the gnu
  libc version is so old (2.5!) that I can't even get the binary packages
  to install.
 
 Silly question, but have you tried *building GHC from source*?
 
 Building GHC is non-trivial, but basically boils down to having an
 existing ghc that runs enough to bootstrap, right? So you can take a
 (quite old, sure, no problem) ghc out of the RHEL 5 repositories and use
 that to build a current GHC 7.6 say.

It's not quite as convenient as that, since you need a new enough GHC to build 
7.6 (not sure which version is required).

So you'd probably need to build one or two intermediate GHCs from source, 
depending on what you can directly install.

Building from source isn't so difficult, you need a gcc, you need to install 
happy and alex (sufficiently old versions for the start, install the newest 
versions before you build the final GHC), and of course a working GHC.

./configure --prefix=$HOME
(or where you want to install GHC)
make  make install

You then have a lot of time to drink tea.

 That _would_ be linked against whatever library stack you have present,
 and you should be ok from there.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 12:50:18, Andres Löh wrote:
 Hi Kazu.
 
 I'd be surprised if zipWith' yields significant improvements. In the
 case of foldl', the strictness affects an internal value (the
 accumulator). However, in the case of zipWith', you're just forcing
 the result a bit more, but I guess the normal use pattern of fibs is
 that you want to see a prefix of the result anyway. So the overall
 amount of evaluation is the same.
 
 I've tried to hack up a quick criterion test comparing my own naive
 zipWith, the Prelude zipWith (which may have additional optimizations,
 I haven't checked), and zipWith':

 
 main :: IO ()
 main = defaultMain $ [
 bench fibs  (nf (take 1 . fibs ) ())
   , bench fibsP (nf (take 1 . fibsP) ())
   , bench fibs' (nf (take 1 . fibs') ())
   ]
 
 The additional () arguments are to prevent GHC from sharing the list
 in between calls. I haven't tested thoroughly if GHC looks through
 this hack and optimizes it anyway.
 
 Compiling without optimization, I get 1.15ms/1.11ms/1.10ms.
 With -O, I get 85us/85us/88us.
 
 Am I overlooking anything? What's your test?

zipWith' would [I haven't tested, but I'm rather confident] make a difference 
if 
you benchmarked

bench name (whnf (fibs !!) 10)

etc.

The reason is that 

foo = initialValues : zipWith f foo (tail foo)

is rather a scan than a real zip, so evaluating an element depends on 
evaluating all previous elements, and thus can build a huge thunk if the 
elements aren't demanded in order.

For a real zip where an element of the result does not depend on the values of 
earlier elements, plain zipWith would perform (usually only marginally) better 
than zipWith'.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 13:06:09, Daniel Fischer wrote:
 
 zipWith' would [I haven't tested, but I'm rather confident] make a
 difference if you benchmarked
 
 bench name (whnf (fibs !!) 10)
 
 etc.

Well, it took a little bit of persuasion to let GHC not cache the list(s), but 
with


fibs :: Int - Integer
fibs k = igo i !! k
  where
i | k  100 = 1
  | otherwise   = 2
igo :: Integer - [Integer]
igo i = let go = 0 : i : zipWith (+) go (tail go) in go

etc., benchmarking

main :: IO ()
main = defaultMain $ [
bench fibs  (whnf fibs 2)
  , bench fibsP (whnf fibsP 2)
  , bench fibs' (whnf fibs' 2)
  ]

shows a clear difference:

benchmarking fibs 
mean: 14.50178 ms, lb 14.27410 ms, ub 14.78909 ms, ci 0.950
benchmarking fibsP
mean: 13.69060 ms, lb 13.59516 ms, ub 13.81583 ms, ci 0.950
benchmarking fibs'
mean: 3.155886 ms, lb 3.137776 ms, ub 3.177367 ms, ci 0.950


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why does not zipWith' exist

2013-02-01 Thread Daniel Fischer
On Friday 01 February 2013, 13:43:59, Andres Löh wrote:
 
 Right, I'm not arguing that it's impossible to produce a difference,
 but I think that if you're defining the sequence of fibs, the most
 likely scenario might be that you're actually interested in a prefix,

Right. If you only want one Fibonacci number with a not too small index, you 
should use a dedicated algorithm.

I was just providing a possible answer to

 Am I overlooking anything? What's your test?

to show how the desire for zipWith' might arise from the fibs example.

 and more importantly, you can still, from the outside, force the
 prefix even if you're only interested in a particular element. The
 second point, imho, is what makes zipWith inherently different from a
 function such as foldl'.

Right, and as I said in my first post, the fibs example is more of a scan than 
a 
zip. And for scans it's natural to consume the list in order [if you only want 
one element, a fold is the proper function].

 You can equivalently define zipWith' as a
 wrapper around zipWith:
 
 zipWith' :: (a - b - c) - [a] - [b] - [c]
 zipWith' f xs ys = strictify (zipWith f xs ys)
   where
 strictify :: [a] - [a]
 strictify []   = []
 strictify (x : xs) = x `seq` x : strictify xs
 
 You cannot easily do the same for foldl and foldl'.

I don't even see how one could do it non-easily.

Cheers,
Daniel___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Package conflicts using cabal-dev

2013-01-30 Thread Daniel Fischer
On Wednesday 30 January 2013, 22:29:23, Arnaud Bailly wrote:

YakGraph.hs:13:30:
Couldn't match expected type `Data.Text.Lazy.Internal.Text'
with actual type `text-0.11.2.0:Data.Text.Lazy.Internal.Text'

one package (at least) you use - probably graphviz - was compiled with a 
version of `text` that is not the newest you have installed.

GHC selects the newest installed version of a package by default, cabal and 
cabal-dev select the version that the other used packages require.

Add a -package text-0.11.2.0 flag to the command line.



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] quotRem and divMod

2013-01-29 Thread Daniel Fischer
On Tuesday 29 January 2013, 03:27:41, Artyom Kazak wrote:
 Hi!
 
 I’ve always thought that `quotRem` is faster than `quot` + `rem`, since
 both `quot` and `rem` are just wrappers that compute both the quotient
 and the remainder and then just throw one out. However, today I looked
 into the implementation of `quotRem` for `Int32` and found out that it’s
 not true:
 
  quotRem x@(I32# x#) y@(I32# y#)
 
  | y == 0 = divZeroError
  | x == minBound  y == (-1) = overflowError
  | otherwise  = (I32# (narrow32Int# (x# `quotInt#`
 
 y#)),
  I32# (narrow32Int# (x# `remInt#`
 y#)))
 
 Why? The `DIV` instruction computes both, doesn’t it? And yet it’s being
 performed twice here. Couldn’t one of the experts clarify this bit?

It's not necessarily performed twice.

func a b = case a `quotRem` b of
 (q, r) - q+r

produces

idivq 8(%rbp)
movq %rax,%rbx
movq $GHC.Int.I32#_con_info,-8(%r12)
movslq %edx,%rax
movslq %ebx,%rbx
addq %rax,%rbx

as the relevant part of the assembly, with only one idivq instruction.

I don't know whether you can rely on the code generator emitting only one 
division instruction in all cases, but in simple cases, it does (on x86_64, at 
least).

Cheers,
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] 9.3 - (2 * 4.5) = 0.3000000000000007

2013-01-16 Thread Daniel Fischer
On Wednesday 16 January 2013, 15:25:15, ivan dragolov wrote:
 9.3 - (2 * 4.5) = 0.3007
 
 I expected 0.3
 
 ?

Prelude Text.FShow.RealFloat FD 9.3
9.300710542735760100185871124267578125

The closest Double to 9.3 is somewhat larger than 9.3. Since the first two 
significant digits are enough to distinguish it from the next smaller number, 
only those are delivered by the Show instance.

If you subtract 9 from that, you get, unsurprisingly,

Prelude Text.FShow.RealFloat it - 9
0.300710542735760100185871124267578125

which is not the closest Double value to 0.3 (in fact, there are 12 Double 
values between that and the closest Double to 0.3). To distinguish that number 
from its neighbours, 16 significant digits are necessary, hence so many are 
displayed.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: crypto-pubkey: all your public key crypto algorithms belong to us.

2013-01-14 Thread Daniel Fischer
On Monday 14 January 2013, 12:36:22, Vincent Hanquez wrote:
 On Sat, Jan 12, 2013 at 02:12:44PM +0100, Ertugrul Söylemez wrote:
   I've spend some good chunk of time adding KATs and tests,
   documentation, and making sure the performance was ahead of other
   haskell implementations.
  
  I suggest looking at Daniel Fischer's arithmoi [1] library, which
  implements very fast Integer operations and should provide most
  functionality needed.  However, beware of timing attacks.
 
 Very cool library and very similar to what crypto-numbers provides albeit
 less sophisticated.

I see you're doing a lot of x `shiftR` 1 with Integers. That's pretty bad for 
performance (at least for integer-gmp, might be not for integer-simple or 
implementations other than GHC [last I looked, JHC didn't have arbitrary 
precision Integers and used 64-bit ones, so it'd be fast there]).

 I wished I knew about it before implementing the
 same(ish) functions.
 
 One caveat of the library is the dependence on integer-gmp.

It was meant to be fast, so exploiting the internal representation of Integers 
in some places was the way to go. I intend to make it portable, but so far am 
too good at procrastinating.  (Making it portable without losing too much 
performance is nontrivial in some places, that contributes.)

Getting a request would make it happen sooner.

 
  Also for the particular purpose of generating safe primes I have written
  a blazingly fast implementation that uses intelligent sieving and finds
  even large primes (= 4096 bits) within seconds or minutes.  It's on
  hpaste [2].  I might turn this into a library at some point.
 
 Seconds or minutes ? that's very different :-)
 But in any case, it would be a nice addition i think.
 
 My safe prime generation function is probably the most naive possible.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] cabal sdist warns about optimization levels

2013-01-13 Thread Daniel Fischer
On Sunday 13 January 2013, 21:27:44, Petr P wrote:
 
 I wonder:
 
 (1) Is there a way how to disable the warning? As the main aim of the
 library is speed, I believe -O2 is appropriate here. And since the code is
 quite short, I'm quite sure the increased compile time won't be noticeable.
 
 (2) Why does cabal complain about it at the first place? I found a
 reference saying the warning is adequate:
 https://github.com/haskell/cabal/issues/808
 but not saying why. Maybe for complex programs -O2 prolongs compile time
 too much, but libraries are usually compiled once and used many times, so
 using -O2 for them seems reasonable in many cases.

Sometimes compiling with -O2 instead of just -O takes significantly longer.
Not always is the produced result faster (often, the results are identical).

So if the code produced with -O performs equally to that produced with -O2, 
and the -O2 compilation takes significantly longer, choosing -O2 imposes a 
cost for no benefit.

That's, I think, why the warning is considered adequate.

You can specify -O2 on a per-module basis with an
{-# OPTIONS_GHC -O2 #-}
pragma where it matters, then cabal won't complain.

Or, if you're too lazy to check the consequences of -O2 vs. -O for each module 
(like I usually am, if there are more than a handful), just verify that -O2 
does indeed make a significant difference for the speed of the result in some 
places without increasing compile time unduly, and henceforth ignore the 
warning if it does. (Re-test every couple of compiler versions.)
After some time, you tend to not even notice it anymore ;)

Cheers,
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ln, e

2013-01-05 Thread Daniel Fischer
On Samstag, 5. Januar 2013, 16:03:23, Christopher Howard wrote:
 Hi. Are natural log and Euler's constant defined somewhere in base, or a
 convenience math module somewhere? I'm having trouble finding them with
 hayoo or system documentation.

The natural logarithm is simply `log`.

Euler's constant isn't defined anywhere, you get it (the best approximation, 
at least very nearly) with `exp 1`.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tail recursive

2012-12-19 Thread Daniel Fischer
On Mittwoch, 19. Dezember 2012, 17:17:19, J.W. Krol wrote:
 From: jkr...@live.com
 To: haskell-cafe@haskell.org
 Subject: Tail recursive
 Date: Wed, 19 Dec 2012 17:07:14 +0100
 
 Hello,
 I need a non tail recursive version of scanl,

scanl isn't tail recursive, I believe you meant you need a tail recursive 
version. But you probably don't.

scanl produces its result incrementally, if it is consumed sequentially (with 
the consumption forcing complete evaluation of the value), each list element 
is evaluated before the next list cells are created, thus no big thunks are 
built.

However, your code below doesn't produce the same result as scanl.
What it produces is

scanl' f q ls = scanr f q (reverse ls)

or

scanl' f q ls = reverse $ scanl (flip f) q ls

reverse is a bad consumer for scanl results, and scanr can have a stack 
overflow problem because it builds its result from the end of the list 
backward to the front. That works well if the function argument is lazy in its 
second argument, but not if it's strict in that - just like foldr.

 to produce a large enough list
 of 100K vectors (vectors defined as a list) I have following code:

 scanl'::(a - a - a) - a - [a] - [a]
 scanl' f q ls  = scanl'' ls (q:[])
   where
 scanl'' (x:xs) ys = let
 h   = head ys
 x'  = f x h
 ys' = x':ys   
  in h `seq` x' `seq` ys' `seq` scanl'' xs ys'
 scanl'' [] ys = ys

The `seq` on ys' does nothing. seq evaluates its first argument to weak head 
normal form (that is, the outermost constructor is determined, for non-
function types) if its result is demanded, but ys' is already in WHNF.

Looking at your use below, your problem is that h and x' are also only 
evaluated to WHNF, which for the case of lists means that it is determined 
whether they are empty or not. Elements of the list are only evaluated if that 
is necessary to determine whether it is empty.

 If I call this function as below I still
 got stack-overflow error: head (scanl' (zipWith (+)) ([0,0]) (take 10
 (repeat [0,1])))

I think the above is only for demonstrative purposes, but

head $ scanl' f q ls

is (with slightly different `seq` behaviour) just

foldl' f q ls

Anyway, your problem is that the `seq`s do not force any of the additions. If 
we look at the first few evaluation steps, we find

scanl'' ([0,1]:xs) [[0,0]]
~ let h = head [[0,0]]
   x' = zipWith (+) [0,1] h
   ys' = x':[[0,0]]
   in h `seq` x' `seq` ys' `seq` scanl'' xs ys'

the initial list is completely evaluated from the start, so the (h `seq`) 
doesn't do anything here. The (x' `seq`) forces

zipWith (+) [0,1] [0,0]

into weak head normal form, giving

(0 + 0) : zipWith (+) [1] [0]

Thus, the next round of scanl'' goes

scanl'' ([0,1]:xs) (((0+0) : zipWith (+) [1] [0]) : [0,0] : [])

Once again, the head of the ys argument is already in WHNF (it was forced in 
the previous round), and the only seq that has any effect is the (x' `seq`), 
which forces

zipWith (+) [0,1] ((0+0) : zipWith (+) [1] [0])

into

(0 + (0+0)) : zipWith (+) [1] (zipWith (+) [1] [0])

When that is continued, lists containing ever larger thunks of the form

(0 + (...  + (0 + 0)...))

respectively

zipWith (+) [1] (zipWith (+) [1] (...(zipWith (+) [1] [0])...))

are built.

To avoid that, you could use deepseq from the Control.DeepSeq module in the 
deepseq package instead of seq (and you only need to deepseq x').

But that's a bit of a sledge hammer, depending on your application, something 
less drastic and more efficient could be possible.

 
 What do I wrong. I am not an experienced Haskell programmer, but find the
 behavior quite unexplainable. Thank for your answer.
 RegardsJacq

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Why is boxed mutable array so slow?

2012-12-01 Thread Daniel Fischer
On Samstag, 1. Dezember 2012, 16:09:05, Branimir Maksimovic wrote:
 All in all even unboxed array is about 10 times slower than Java version.
 I don't understand why is even unboxed array so slow.

It's not the unboxed arrays that are slow.

Your code has a couple of weak spots, and GHC's native code generator has a 
weakness that bites here.

On my box, I don't quite have a 10× difference to my translation to Java, it's 
a bit less than 7× (0.82s vs 0.12s - I don't want to bring my box to its knees 
by running something that takes 3GB+ of RAM, so I run the unboxed array part 
only) with the LLVM backend and 8× (0.93s) with the native code generator. 
That's in the same ballpark, though.

So what's the deal?

Main.main_$s$wa1 [Occ=LoopBreaker]
  :: GHC.Prim.Int#
 - GHC.Prim.Int#
 - GHC.Prim.State# GHC.Prim.RealWorld
 - GHC.Types.Int
 - GHC.Types.Int
 - GHC.Types.Int
 - ...

Your loops carry boxed Ints around, that's always a bad sign. In this case it 
doesn't hurt too much, however, since these values are neither read nor 
substituted during the loop (they're first and last index of the array and 
number of elements). Additionally, they carry an IOUArray constructor around. 
That is unnecessary. Eliminating a couple of dead parameters


init' a = do
(_,n) - getBounds a
let init k
  | k  n = return ()
  | otherwise = do
  let x = fromIntegral $ k + k `div` 3
  unsafeWrite a k x
  init (k+1)
init 0

partial_sum a = do
(_,n) - getBounds a
let ps i s
  | i  n = return ()
  | otherwise = do
  k - unsafeRead a i
  let l = s + k
  unsafeWrite a i l
  ps (i+1) l
k - unsafeRead a 0
ps 1 k

brings the time for the native code generator down to 0.82s, and for the LLVM 
backend the time remains the same.

Next problem, you're using `div` for the division.

`div` does some checking and potentially fixup (not here, since everything is 
non-negative) after the machine division because `div` is specified to satisfy

a = (a `div` b) * b + (a `mod` b)

with 0 = a `mod` b  abs b.

That is in itself slower than the pure machine division you get with quot.

So let's see what we get with `quot`.

0.65s with the native code generator, and 0.13 with the LLVM backend.

Whoops, what's that?

The problem is, as can be seen by manually replacing k `quot` 3 with

(k *2863311531) `shiftR` 33

(requires 64-bit Ints; equivalent in Java: k*28..1L  33), when the native 
backend, the LLVM backend and Java (as well as C) all take more or less the 
same time [well, the NCG is a bit slower than the other two, 0.11s, 0.11s, 
0.14s], that division is a **very** slow operation.

Java and LLVM know how to replace the division by the constant 3 with a 
mulitplication, a couple of shifts and an addition (since we never have 
negative numbers here, just one multiplication and shift suffice, but neither 
Java nor LLVM can do that on their own because it's not guaranteed by the 
type). The native code generator doesn't - not yet.

So the programme spends the majority of the time dividing. The array reads and 
writes are on par with Java's (and, for that matter, C's).

If you make the divisor a parameter instead of a compile time constant, the 
NCG is not affected at all, the LLVM backend gives you equal performance (it 
can't optimise a division by a divisor it doesn't know). Java is at an 
advantage there, after a while the JIT sees that it might be a good idea to 
optimise the division and so its time only trebles.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Vedr: To my boss: The code is cool, but it is about 100 times slower than the old one...

2012-11-29 Thread Daniel Fischer
On Donnerstag, 29. November 2012, 21:00:36, Fixie Fixie wrote:
 The program seems to take around 6 seconds on my linux-box, while the c
 version goes for 0.06 sekcond.
 
 That is really some regression bug :-)
 
 Anyone with a more recent version thatn 7.4.1?

I don't even have a problem with 7.4.1:

$ for ghc in $GHCS; do echo $ghc; time ./hskahan-$ghc  /dev/null; done;
7.0.4

real0m0.217s
user0m0.214s
sys 0m0.002s
7.2.1

real0m0.197s
user0m0.194s
sys 0m0.002s
7.2.2

real0m0.187s
user0m0.187s
sys 0m0.000s
7.4.1

real0m0.253s
user0m0.249s
sys 0m0.003s
7.4.2

real0m0.250s
user0m0.247s
sys 0m0.002s
7.6.1

real0m0.224s
user0m0.221s
sys 0m0.002s

$ time ./ckahan  /dev/null

real0m0.102s
user0m0.079s
sys 0m0.022s


We have an unpleasant regression in comparison to 7.2.* and the 7.4.* were 
slower than 7.6.1 is, but it's all okay here (not that it wouldn't be nice to 
have it faster still).

Are you on a 32-bit system?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Vedr: To my boss: The code is cool, but it is about 100 times slower than the old one...

2012-11-29 Thread Daniel Fischer
On Donnerstag, 29. November 2012, 13:40:42, Johan Tibell wrote:
 word2Double :: Word - Double
 word2Double (W# w) = D# (int2Double# (word2Int# w))
 
 On my (64-bit) machine the Haskell and C versions are on par.

Yes, but the result is very different.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Vedr: To my boss: The code is cool, but it is about 100 times slower than the old one...

2012-11-29 Thread Daniel Fischer
On Donnerstag, 29. November 2012, 13:40:42, Johan Tibell wrote:
 
 word2Double :: Word - Double
 word2Double (W# w) = D# (int2Double# (word2Int# w))
 
 On my (64-bit) machine the Haskell and C versions are on par.

On my box, the Haskell is even faster then, but, as said, the result is 
incorrect

With

correction :: Double
correction = 2 * int2Double minBound

word2Double :: Word - Double
word2Double w = case fromIntegral w of
   i | i  0 - int2Double i - correction
 | otherwise - int2Double i

I get

real0m0.078s
user0m0.077s
sys 0m0.001s

with correct results.

Okay, we **need** a better Word - Double etc. conversion. We could start with 
the above, that seems not too shabby.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange behavior with listArray

2012-11-12 Thread Daniel Fischer
On Montag, 12. November 2012, 08:36:49, Bas van Dijk wrote:
 On 12 November 2012 04:50, Alex Stangl a...@stangl.us wrote:
  I'm stymied trying to figure out why the program below blows up with
  loop when I use f 0
 
 If you replace the a!0 in f by its value 0, f is equivalent to:
 
 f k = if k  0
 then f 0
 else 0 : f 1
 
 Do you see the loop now?

I see no loop in that, and ghci doesn't either:

Prelude let f :: Int - [Int]; f k = if k  0 then f 0 else 0 : f 1
Prelude take 5 $ f 1
[0,0,0,0,0]

and if you use (f 0) instead of (f (a!0)) there, it works.

 
 Maybe you meant f to be:
 
 f k = if k  0
 then f (a!k)
 else 0 : f 1

Loops too.

The problem, Alex, is that

f k = if k  0
then f (a!0)
else 0 : f 1

is strict, it needs to know the value of (a!0) to decide which branch to take. 
But the construction of the array a needs to know how long the list (0 : f 0) 
is (well, if it's at least four elements long) before it can return the array. 
So there the cat eats its own tail, f needs to know (a part of) a before it 
can proceed, but a needs to know more of f to return than it does.

g and h  are not strict, they simply let the construction write thunks into 
the array elements, and those can then later be evaluated after the 
construction of a has returned.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trying to use more than one array in runSTUArray

2012-03-15 Thread Daniel Fischer
On Thursday 15 March 2012, 19:27:18, Juan Miguel Vilar wrote:
 Hello, café:
 
 I am trying to use more than one array with runSTUArray but I don't seem
 to be able to understand how it works. My first try is this:
 
 test1 n = runSTUArray $ do
   a - newArray (1, n) (2::Int)
   b - newArray (1, n) (3::Int)
   forM_ [1..n] $ \i - do
 v - readArray a i
 writeArray b i (v+1)
   return b
 
 but it does not work.

The compiler can infer the type of b (STUArray s Integer Int), since that 
is returned (and then frozen to a UArray Integer Int), but it cannot infer 
what array type to use for a. Thus that function does not compile.

 However, when I write
 
 test2 n = runSTUArray $ do
   let createArray v n = newArray (1, n) (v::Int)

Here you create a local binding for createArray that gets a monomorphic 
type, that type is the fixed by the returning of b to

createArray :: Int - Integer - ST s (STUArray s Integer Int)

you can make that fail too with enabling {-# LANGUAGE NoMonoLocalBinds #-}

   a - createArray 2 n
   b - createArray 0 n
   forM_ [1..n] $ \i - do
 v - readArray a i
 writeArray b i (v+1)
   return b
 
 everything is fine although I expected the two versions to be
 equivalent. To further complicate matters, the following
 
 createArray v n = newArray (1, n) (v::Int)

This is a top-level definition, createArray is bound by a function binding, 
hence it is polymorphic again, and as in the first case, the type of a 
cannot be inferred. Give it a type signature

createArray :: Int - Int - ST s (STUArray s Int Int)

(I chose Int for the indices here instead of the default Integer)

 
 test3 n = runSTUArray $ do
   a - createArray 2 n
   b - createArray 3 n
   forM_ [1..n] $ \i - do
 v - readArray a i
 writeArray b i (v+1)
   return b
 
 does not work either. Where can I find an explanation for this
 behaviour? Furthermore, what I am after is to use two arrays with
 different types (Int and Bool), is it possible?

Sure, you need to use type signatures.

With expression type signatures, it would look like

test1 n = runSTUArray $ do
  a - newArray (1, n) 2 :: ST s (STUArray s Int Int)
  b - newArray (1, n) 3 :: ST s (STUArray s Int Int)
  forM_ [1..n] $ \i - do
v - readArray a i
writeArray b i (v+1)
  return b

If you don't want to give expression type signatures at every use, you can 
create a top-level function

{-# LANGUAGE FlexibleContexts #-}

createArray :: (Marray (STUArray s) a (ST s)) = a - Int - ST s (STUArray 
s Int a)
createArray v n = newArray (1,n) v

and you have to deal with only one type signature.

 
Thanks in advance,
 
Juan Miguel


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Trying to use more than one array in runSTUArray

2012-03-15 Thread Daniel Fischer
On Thursday 15 March 2012, 19:53:56, Daniel Fischer wrote:
 On Thursday 15 March 2012, 19:27:18, Juan Miguel Vilar wrote:
  Hello, café:

 
  However, when I write
  
  test2 n = runSTUArray $ do
  
let createArray v n = newArray (1, n) (v::Int)
 
 Here you create a local binding for createArray that gets a monomorphic
 type, that type is the fixed by the returning of b to
 
 createArray :: Int - Integer - ST s (STUArray s Integer Int)
 
 you can make that fail too with enabling {-# LANGUAGE NoMonoLocalBinds
 #-}

Hmm, what compiler version are you using? When I actually tried to compile 
that, it failed with

No instance for (MArray a0 Int (ST s))

without language extensions. After enabling MonoLocalBinds, however, it 
compiled with 6.12.3, 7.0.2, 7.0.4, 7.2.1 and 7.2.2, but 7.4.1 still 
refused to compile it.

 
a - createArray 2 n
b - createArray 0 n
forM_ [1..n] $ \i - do

  v - readArray a i
  writeArray b i (v+1)

return b
  
  everything is fine although I expected the two versions to be
  equivalent.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: combinatorics

2012-02-05 Thread Daniel Fischer
On Wednesday 01 February 2012, 07:53:03, wren ng thornton wrote:
  The primes function in the combinat package is based on an old Cafe
  thread, and actually seems to be faster than the one in the
  combinatorics package.

Yes, but it has a memory leak. On my box at least, with ghc 6.12, 7.0 and 
7.2.

 
 The primes generator was some old code I had laying around for one of 
 those online programming challenges; fast enough for the task.
 I'll  probably trade it in for your algorithm though.

Why not use one of the packages on hackage which offer faster prime 
generators?

I'm aware of the following usable packages:

- primes: decentish performance if you don't need to sieve high, but not 
recommendable if you want to sieve above ~10^7, in my measurements about 
the same performance as the algorithm used in combinat, but without memory 
leak.

- NumberSieves: The O'Neill sieve, about twice as fast as the primes sieve, 
uses less memory (and scales better if you want to sieve to higher limits).

- arithmoi: A segmented Eratosthenes sieve using mutable unboxed arrays. 
Much faster than the above and uses less memory.
If you don't like arrays, it also has a priority queue sieve similar to the 
O'Neill sieve, but with a more efficient PQ implementation.

 One of the things
 I'm disappointed by about the current implementation is the memory
 overhead for storing the primes. It'd be nice to use chunked arrays of
 unboxed integers in order to remove all the pointers; but my attempt at
 doing so  had catastrophic performance...

arithmoi's Eratosthenes sieve offers the option to get a list of sieve 
chunks, basically UArray Int Bool, which gives far more compact storage 
than a list of Integers (~33KB per million range, much more compact than an 
unboxed array of primes for the reachable ranges) from which the list of 
primes can rather efficiently obtained when needed. That may do what you 
want well enough.

Cheers,
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: combinatorics

2012-02-05 Thread Daniel Fischer
On Sunday 05 February 2012, 23:14:35, wren ng thornton wrote:
 On 2/5/12 10:21 AM, Daniel Fischer wrote:
  Why not use one of the packages on hackage which offer faster prime
  generators?
 
 Mostly because I hadn't looked, having had the code already laying
 around.

Yeah, that's fine, it was just

  I'll  probably trade it in for your algorithm though.

that made me wonder.

 I'm not opposed to it, however another goal is to remain
 portable to other compilers, which means being H98/H2010 compliant.

A noble goal.

 NumberSieves uses BangPatterns, but that would be easily remedied if the
 author is willing; arithmoi looks quite nice, however it is GHC-only.

The curse of striving for efficiency.
Portability is on the to-do list (with low priority, however).
It just climbed a place.

Cheers,
Daniel


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Natural Transformations and fmap

2012-01-23 Thread Daniel Fischer
On Tuesday 24 January 2012, 04:39:03, Ryan Ingram wrote:
 At the end of that paste, I prove the three Haskell monad laws from the
 functor laws and monoid-ish versions of the monad laws, but my proofs
 all rely on a property of natural transformations that I'm not sure how
 to prove; given
 
 type m :- n = (forall x. m x - n x)
 class Functor f where fmap :: forall a b. (a - b) - f a - f b
 -- Functor identity law: fmap id = id
 -- Functor composition law fmap (f . g) = fmap f . fmap g
 
 Given Functors m and n, natural transformation f :: m :- n, and g :: a
 - b, how can I prove (f . fmap_m g) = (fmap_n g . f)?

Unless I'm utterly confused, that's (part of) the definition of a natural 
transformation (for non-category-theorists).

 Is there some
 more fundamental law of natural transformations that I'm not aware of
 that I need to use?  Is it possible to write a natural transformation
 in Haskell that violates this law?
 
   -- ryan


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function composition

2012-01-15 Thread Daniel Fischer
On Sunday 15 January 2012, 16:17:24, TP wrote:
 Hi,
 
 I have a basic question concerning function composition. I have used
 http://www.haskell.org/tutorial/functions.html
 to write a composition function:
 
 Prelude let f°g = f g

This does not what you probably expect. That definition means (°) = ($) is 
just function application, or, in other words, (°) is the identity function 
restricted to function types.

If I'm correct in suspecting you want function composition,

Prelude let f°g = f . g
Prelude let (°) = (.)
Prelude let (f ° g) x = f (g x)

are possible ways to obtain that.

 Prelude let p = (*2)
 Prelude let q = (+3)

These two lead to the surprise below.

 Prelude p°q 4

This is parsed as

 p ° (q 4)

 14
 Prelude :t (°)
 (°) :: (t1 - t) - t1 - t

(°) is the identity restricted to function types.

 
 If I understand well, this means that the infix operator ° takes a
 function of type t1, i.e. g in f°g,

it may be a function, but need not, it could also be a non-function value 
like [], True, ...

 and applies f on it, which takes a
 type t1 as input and returns f(g) which is of type t. The final result
 is of type t. So the first argument is represented above by (t1-t),
 and the second by t1, the final result being of type t.
 
 However, I am not able to get the type of p°q
 
 Prelude :t p°q
 
 interactive:1:3:
 Couldn't match expected type `Integer'
 with actual type `Integer - Integer'
 In the second argument of `(°)', namely `q'
 In the expression: p ° q
 Prelude
 
 What's the problem here?

1. The monomorphism restriction. You have bound p and q

Prelude let p = (*2)
Prelude let q = (+3)

with simple pattern bindings (plain variable name, no function arguments in 
the binding) and without type signature. The inferred most general type for 
both is

Num a = a - a

which is a constrained polymorphic type.

The monomorphism restriction (language report, section 4.5.5) says such 
bindings must have a monomorphic type.

By the defaulting rules (section 4.3.4), the type variable is defaulted to 
Integer to obtain a monomorphic type. Hence in your session, you have

p, q :: Integer - Integer

Now, (°) :: (a - b) - a - b, and matching p's type with the type of 
(°)'s first argument, a = b = Integer. But if we try to match q's type with 
the type of (°)'s second argument, that type has already been determined to 
be Integer here, so q's type (Integer - Integer) doesn't match.

2. Even with the monomorhism eliminated, by one (or more) of

a) binding p and q with a function binding (let p x = x * 2)
b) giving a type signature for the binding
c) disabling the MR (Prelude :set -XNoMonomorphismRestriction)

you still get something probably unexpected. now

p :: Num a = a - a
q :: Num b = b - b

unifying p's type with the type of (°)'s first argument,

(p °) :: Num a = a - a

Now we must unify a with q's type, thus

(p ° q) :: (Num b, Num (b - b)) = b - b

 How can I obtain the type of p°q?

Eliminate the MR from the picture.

 
 Thanks in advance,
 
 TP


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Text.Regex.Base throws exceptions with makeRegexOptsM

2011-12-29 Thread Daniel Fischer
On Thursday 29 December 2011, 23:52:46, Omari Norman wrote:
 Hi folks,
 
 I'm using Text.Regex.Base with the TDFA and PCRE backends. I want to
 compile regular expressions first and make sure the patterns were
 actually valid, so I used makeRegexOptsM, which indicates a bad regular
 expression by calling fail. That allows you to use makeRegexOptsM with
 Maybe or with (Either String) (assuming that Either String is an
 instance of Monad, which of course is defined in Control.Monad.Error.)
 
 Doing this with Maybe Regex works like it should--bad pattern gives you
 a Nothing. But if you want to see the error message by using Either
 String, an exception gets thrown with the bad pattern, rather than
 getting a Left String.
 
 Why is this?

The cause is that a pattern-match failure in a do-block or equivalent 
causes the Monad's 'fail' method to be invoked.

For Maybe, we have

fail _ = Nothing

For Either, there used to be

instance Error e = Monad (Either e) where
...
fail s = Left (strMsg s)

in mtl's Control.Monad.error, and all was fine if one used the regex 
functions with e.g. (Either String) as the Monad.

Recently, however, it was decided to have

instance Monad (Either e) where
...
fail s = error s -- not explicitly, but by Monad's default method

in Control.Monad.Instances. So now, if you have a pattern-match failure 
using (Either String), you don't get a nice 'Left message' but an error.

So why was it decided to have that change?

'fail' doesn't properly belong in the Monad class, it was added for the 
purpose of dealing with pattern-match failures, but most monads can't do 
anything better than abort with an error in such cases.
'fail' is widely considered a wart.

On the other hand, the restriction to Either's first parameter to belong to 
the Error class is artificial, mathematically, (Either e) is a Monad for 
every type e. And (Either e) has use-cases as a Monad for types which 
aren't Error members.

So the general consensus was that it was better to get rid of the arbitrary 
(Error e) restriction.

Now, what can you do to get the equivalent of the old (Either String)?

Use 'ErrorT String Identity'.

It's a bit more cumbersome to get at the result,

foo = runidentity . runErrorT $ bar

but it's clean.

 Seems like an odd bug somewhere.

A change in behaviour that was accepted as the price of fixing what was 
widely considered a mistake.

 I am a Haskell novice, but
 I looked at the code for Text.Regex.Base and for the TDFA and PCRE
 backends and there's nothing in there to suggest this kind of
 behavior--it should work with Either String.

It used to.

 
 The attached code snippet demonstrates the problem. I'm on GHC 7.0.3
 (though I also got the problem with 6.12.3) and regex-base-0.93.2 and
 regex-tdfa-1.1.8 and regex-pcre-0.94.2. Thanks very much for any tips or
 ideas. --Omari


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Recommended class instances for container type

2011-12-08 Thread Daniel Fischer
On Thursday 08 December 2011, 18:13:50, Christoph Breitkopf wrote: 
 Well, including a some file via CPP did look experimental enough to me.
 I'd like to stay away from GHC-only code, if possible.

CPP is standard (maybe not in the sense that it's included in the language 
standard, but every implementation I'm aware of supports CPP).

 
  At some point, if you want your container class to be useful to
  others, you'll want to implement Foldable and Traversable.
 
 Being useful to others would be the whole point in releasing it at all
 :-)
 
 Thanks for your explanations - I take this as: Yes, the Haskell
 community is really using all this stuff in production code, so better
 offer it, or your library might not be that usable.

To varying extent. Stuff can be quite usable without Data or Typeable 
instances. You can start with what you consider most important and add the 
rest when you get feature requests.

 I'll try to be complete, then.
 
 - Chris


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] List x ByteString x Lazy Bytestring

2011-12-05 Thread Daniel Fischer
On Monday 05 December 2011, 14:14:56, John Sneer wrote:
 I've used Haskell and GHC to solve particular real life application. 4
   tools were developed and their function is almost the same - they
   modify textual input according to patterns found in the text. Thus, it

Hmm, modification can be a problem for ByteStrings, since it entails 
copying. That could be worse for strict BytStrings than lazy, if in the 
lazy ByteString you can reuse many chunks.

   is something like a compiler, the result is also a text and it is not
   parsed to tokens as patterns appear on a different level.
 
   The tools differ in tasks and number of modifications performed,
   otherwise, in principal, they are very much similar.
 
   I used lists (Prelude, Data.List) to develop the tools. After
   successfully completing the development, I've started to optimize the
   code to make the tools faster. After modification of some algorithms
   (which dropped the processing time notably), I started to change data
   structures. I swapped lists with lazy bytestrings. Nevertheless, what
   an unpleasant surprise, the processing speed dropped down,
   significantly / more then 30% time needed). 

Two main possibilities:
1. your algorithm isn't suited for ByteStrings
2. you're doing it wrong

The above indicates 1., but without a more detailed description and/or 
code, it's impossible to tell.

 
   So my questions follow:
 - What kind of application is lazy bytestring suitable for?

Anything that involves examining large sequences of bytes (or ASCII 
[latin1/other single-byte encoding] text) basically sequentially (it's not 
good if you have to jump forwards and backwards a lot and far).
Also some types of modification of such data.

 - Would it be worth using strict bytestring even if input files may be
 large? (They would fit in memory, but may consume whole)

Probably not, see above. But see above.

 - If bytestring is not suitable for text manipulation, is there
 something faster than lists?

text has already been mentioned, but again, there are types of manipulation 
it's not well-suited for and where a linked list may be superior.

 - It would be nice to have native sort for lazy bytestring - would it be
 slower than  pack $ Data.List.sort $ unpack ?

The natural sort for ByteStrings would be a counting sort,
O(alphabet size + length), so for long ByteStrings, it should be 
significantly faster than pack . sort . unpack, but for short ones, it 
would be significantly slower.

 - If bytestring is suitable for text manipulation could we have some
 hGetTextualContents which translates Windows EOL (CR+LF) to LF?

Doing such a transformation would be kind of against the purpose of 
ByteStrings, I think.  Isn't the point of ByteStrings to get the raw bytes 
as efficiently as possible?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get a file path to the program invoked?

2011-12-05 Thread Daniel Fischer
On Monday 05 December 2011, 15:53:35, dokondr wrote:
 Balazs, thanks for your comments!
 The first comment works just fine.
 With / operator I get this:
 
 Main System.Environment.Executable System.FilePath /abc / /
 /
 
 Instead of getting /abc/ I get /. What am I doing wrong?

The second path is absolute.

/ is an alias for combine, the docs for that say:

Combine two paths, if the second path isAbsolute, then it returns the 
second.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Poll: Do you want a mascot? -- please stop this

2011-12-05 Thread Daniel Fischer
On Monday 05 December 2011, 17:03:35, Mark Lentczner wrote:
 On 23/11/11 19:11, heathmatlock wrote:
  Question: Do you want a mascot?
 
 No.

I thought it was dead. Since it isn't: also no.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Poll: Do you want a mascot?

2011-11-25 Thread Daniel Fischer
On Friday 25 November 2011, 09:28:29, Ivan Lazar Miljenovic wrote:
 On 25 November 2011 19:13, Liyang HU haskell@liyang.hu wrote:
  heathmatlock heathmatlock at gmail.com writes:
  Question: Do you want a mascot?
  Yes
  
  And we already have one: http://paraiso-lang.org/ikmsm/books/c80.html
 
 Uh. W...T...F...???

Exactly my thoughts.

 
 Do I want to know what's going on there? :p

I don't think so.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Decision procedure for foldr/foldl/foldl'?

2011-11-20 Thread Daniel Fischer
On Sunday 20 November 2011, 17:28:43, David Fox wrote:
 Does anyone have a quick way to decide which of the fold functions to
 use in a given situation?  There are times when I would like to find
 out which to use in the quickest way possible, rather than reading a
 long explanation of why each one behaves the way it does.
 

- foldl: In the rare cases where you need this, you'll probably know (I'm 
not aware of any real-world case where foldl is the correct choice)

Rule of thumb:

Can the result be determined/constructed (at least partially) before the 
end of the list has been reached?[*]
Then foldr.
Otherwise foldl'.

Exceptions to the rule may exist.

[*] That typically means the folded function is lazy in its second 
argument, like (:), (++), (), (||) ...

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ST not strict enough?

2011-11-18 Thread Daniel Fischer
On Friday 18 November 2011, 11:18:33, Yves Parès wrote:
 Instead of rewriting modifySTRef, why not just do :
 
 modifySTRef counter (\x - let y = x+1 in y `seq` y)
 
 Is there a problem with that?

Yes, y `seq` y is precisely the same as y.

a `seq` b means whenever evaluation of b is demanded, also evaluate a (to 
WHNF).
So y `seq` y ~ whenever evaluation of y is demanded, also evaluate y.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ST not strict enough?

2011-11-18 Thread Daniel Fischer
On Friday 18 November 2011, 13:05:06, Yves Parès wrote:
 ...so there is no way to do that inside the function passed to
 modifySTRef? In other words, there is no way to ensure inside a
 function that its result will be evaluated strictly?

Well,

modifySTRef ref fun = do
val - readSTRef ref
writeSTRef ref  (fun val)

(resp.
modifySTRef ref f = writeSTRef ref . f = readSTRef ref
as it's actually written in Data.STRef).

What's written to ref is the thunk (fun val), meaning, when the value is 
demanded, evaluate fun applied to the argument val.

So, no, the function is not entered before the result is demanded, hence it 
can't.
It can ensure that the result is evaluated to a deeper level than required 
by the calling context when the function is entered, though.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ST not strict enough?

2011-11-16 Thread Daniel Fischer
On Wednesday 16 November 2011, 22:45:16, Johan Tibell wrote:
 On Wed, Nov 16, 2011 at 12:33 PM, Antoine Latter aslat...@gmail.com 
wrote:
  We already have one in base - it re-exports Data.STRef in whole :-)
  
  
  http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-STRef-
  Strict.html
 
 Then it's wrong. :( In what sense is it strict?

In the sense of Control.Monad.ST.Strict vs. Control.Monad.ST.Lazy

 I think it should be strict in the value stored in the ref.

Yes, we probably need that.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problems with installing the correct version of process. Help?

2011-11-15 Thread Daniel Fischer
On Tuesday 15 November 2011, 22:34:17, Blaine wrote:
 Great question. How does one ignore the warning?

Not.

process and directory are boot packages, required by ghc  and indirectly by 
many of the packages you install(ed).
Having multiple versions of these spells trouble and breakage.
Read http://www.vex.net/~trebla/haskell/sicp.xhtml for more.

You already have two versions of directory, the one ghc was built with and 
1.1.0.1. It's not unlikely that you already have some unusable packages due 
to that.

$ ghc-pkg check

should tell you about such.
You should unregister the duplicate directory (1.1.0.1, *keep the one ghc 
was built with*) and all packages depending on it.
Then you can try to reinstall those packages, before cabal installing 
anything, you should check with --dry-run whether it would install a new 
version of any of the boot packages (basically everything coming with ghc 
itself, but having a newer version of Cabal is okay). If it would, stop.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] deepseq-1.2.0.1 missing Data.Map instance

2011-11-15 Thread Daniel Fischer
On Tuesday 15 November 2011, 23:26:04, Henry Laxen wrote:
  So I
 guess my question is:  Is there a reason that the map instance was
 removed from deepseq-1.2.0.1,

Yes.

 and can we please put it back in?

No.



The NFData instance has been moved to the containers package, where it can 
be more efficiently done. The change is already in the latest released 
deepseq version, but will only be in the containers version to be released 
with ghc-7.4.

For your unfortunate combination, consider reverting to a prior deepseq 
version, or manually provide the instance where needed (I recommend the 
former).

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Strange GC timings

2011-11-12 Thread Daniel Fischer
On Saturday 12 November 2011, 20:36:04, Artyom Kazak wrote:
 Hello!
 
 The following program executes 1.5 seconds on my computer:
 
 ---CODE BEGIN-
  module Main where
 
  import Data.Array.IArray
 
  main = print (answers ! 100)
 
  nextAns :: (Int, Int, Float) - (Int, Int, Float)
  nextAns (a, n, r) = if r2  1 then (a+1, n+2, r2) else (a+1, n+3,
 r3) where
  a' = fromIntegral a
  n' = fromIntegral n
  r2 = r * (a'/(a'+1))**n' * (n'+1)*(n'+2)/(a'+1)^2
  r3 = r2 * (n'+3) / (a'+1)
 
  answers :: Array Int Int
  answers = listArray (1, 100) (map snd3 $ iterate nextAns (1, 2,
 2)) where snd3 (a, b, c) = b
 CODE END--

Can't reproduce. The IArray version needs more than 16M of stack here (16M 
wasn't enough, 32M was), that gives a hint.
IArray took 0.20s MUT and 0.38s GC, UArray took 0.19s MUT.

But of course, I compiled with optimisations, which you apparently didn't.

However, compiling without optimisations for the sake of investigation, I 
get numbers closer to yours, yet still distinct enough.

UArray took 1.28s MUT, 0.02s GC, that corresponds pretty well to your 
result.
IArray took 1.32s MUT and 0.56s GC. [*]
So that conforms with my -O2 results, UArray is a wee bit faster in the 
calculation, the big difference is GC, but not with your results.

[*] That was with 7.2.2, I tried also with 7.0.4, that made no difference 
for UArray, but for the boxed array:

  MUT   time1.31s  (  1.31s elapsed)
  GCtime   21.31s  ( 21.34s elapsed)

Ouch!

 
  From these 1.5 seconds, 1 second is spent on doing GC. If I run it with
 -A200M, it executes for only 0.5 seconds (total).
 
 Which is more interesting, when I use UArray instead of Array, it spends
 only 0.02 seconds in GC, but total running time is still 1.5 seconds.
 
 Why are... these things?

If you're using a boxed array, you
- are building a long list of thunks with iterate (no strictness, so 
nothing is evaluated)
- are then writing the thunks to the boxed array (actually, this is 
interleaved with the construction)
- finally evaluate the last thunk, which forces the previous thunks, 
peeling layers off the thunk, pushing them on the stack until the start is 
reached, then popping the layers and evaluating the next term.

You get a huge thunk that takes long to garbage-collect when it finally can 
be collected.

Using an unboxed array, you have to write the *values* to the array as it 
is constructed, that forces evaluation of the iterate-generated tuples 
immediately, hence no big thunk is built and the small allocations can very 
quickly be collected.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Bounds checking pragma?

2011-11-09 Thread Daniel Fischer
On Thursday 10 November 2011, 00:35:07, Artyom Kazak wrote:
 Hello!
 
 The (!) operator is short and nice. Unfortunately, when doing heavy
 computing, we have to use unsafeAt instead. It looks ugly and it is
 ugly, also.
 
 Some compilers for imperative languages like Free Pascal have an option
 to turn on/off bounds checking for arrays. Wouldn't it be nice to have
 such option in GHC? Is it possible?
 
 There is a problem: Haskell has a lot of array libraries. The only
 solution I see is a new FLAG pragma:
 
   (!) :: Array i a - i - a
  --definition
 
  {-# FLAG boundsCheck (!) = unsafeAt #-}

There's a problem here, unsafeAt uses an Int index into the array, while 
(!) uses the declared index type. Even skipping the bounds check, you'd 
still have to calculate the Int index for the replacement of (!).

 
 It is similar to RULES pragma, but only fires when flag is set. To set
 the flag you need to complile with option -flags=boundsCheck. Also,
 the mantainers of vector library, bytestring library, repa library and
 so on will have to include such pragmas in their code.
 
 I don't know about C++ preprocessor, though. Maybe this is already
 solvable with #define's...

#ifdef OMIT_BOUNDS_CHECK
{-# RULES
ArrayIndex  arr ! i = unsafeAt arr (unsafeIndex (bounds arr) i) 
 #-}
#endif

 
 Anyway, I have to say it once again: unsafeAt is ugly and Haskell is
 beautiful. Why high-performance code should be ugly?

(?) = unsafeAt


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project Euler Problem 357 in Haskell

2011-11-08 Thread Daniel Fischer
On Tuesday 08 November 2011, 12:21:14, mukesh tiwari wrote:
 Hello all
 Being a Haskell enthusiastic , first I tried to solve this problem in
 Haskell but it running for almost 10 minutes on my computer but not
 getting the answer.

Hmm, finishes in 13.36 seconds here, without any changes.
Of course, it has to be compiled with optimisations, ghc -O2.

 A similar C++ program outputs the answer almost instant

2.85 seconds. g++ -O3.
So, yes, much faster, but not orders of magnitude.

 so could some one please tell me how to improve this Haskell
 program.
 
 import Control.Monad.ST
 import Data.Array.ST
 import Data.Array.Unboxed
 import Control.Monad
 
 prime :: Int - UArray Int Bool
 prime n = runSTUArray $ do
 arr - newArray ( 2 , n ) True :: ST s ( STUArray s Int Bool )
 forM_ ( takeWhile ( \x - x*x = n ) [ 2 .. n ] ) $ \i - do
 ai - readArray arr i
 when ( ai  ) $ forM_ [ i^2 , i^2 + i .. n ] $ \j - do
 writeArray arr j False
 
 return arr

Hmm, would have to look at the core, if the optimiser isn't smart enough to 
eliminate the lists, you get considerable overhead from that.

Anyway, readArray/writeArray perform bounds checks, you don't have that in 
C++, so if you use unsafeRead and unsafeWrite instead, it'll be faster.
(You're doing the checks in *your* code, no point in repeating it.)

 
 pList :: UArray Int Bool
 pList = prime $  10 ^ 8
 
 divPrime :: Int - Bool
 divPrime n = all ( \d - if mod n d == 0 then pList ! ( d + div  n  d )
 else True )  $  [ 1 .. truncate . sqrt . fromIntegral  $ n ]

Use rem and quot instead of mod and div.
That doesn't make too much difference here, but it gains a bit.

That allocates a list, if you avoid that and check in a loop, like in C++, 
it'll be a bit faster.
And instead of (!), use unsafeAt to omit a redundant bounds-check.

 
 
 main = putStrLn . show . sum  $ [ if and [ pList ! i , divPrime . pred $
 i ] then pred  i else 0 | i - [ 2 .. 10 ^ 8 ] ]

Dont use

and [condition1, condition2]

that's more readable and faster if written as

condition1  condition2

Don't use pred, use (i-1) instead.

And you're gratuitously adding a lot of 0s, filter the list

sum [i | i - [1 .. ], pList ! (i+1)  divPrime i]

However, you're allocating a lot of list cells here, it will be faster if 
you calculate the sum in a loop, like you do in C++.

Eliminating the unnecessary bounds-checks and the intermediate lists, it 
runs in 4.3 seconds here, not too bad compared to the C++.

However, use a better algorithm.
As is, for each prime p you do trial division on (p-1). For every (p-1) 
satisfying the criterion, you do about sqrt(p-1) divisions, that costs a 
lot of time. You can make the factorisation (and hence finding of divisors) 
cheap if you slightly modify your sieve.

 
 
 C++ program which outputs the answer almost instant.
 
 #includecstdio
 #includeiostream
 #includevector
 #define Lim 10001
 using namespace std;
 
 bool prime [Lim];
 vectorint v ;
 
 void isPrime ()
  {
   for( int i = 2 ; i * i = Lim ; i++)
if ( !prime [i]) for ( int j = i * i ; j = Lim ; j += i ) 
 prime 
[j]
 = 1 ;
 
   for( int i = 2 ; i = Lim ; i++) if ( ! prime[i] ) v.push_back( 
 i ) 
;
   //coutv.size()endl;
   //for(int i=0;i10;i++) coutv[i] ;coutendl;
 
  }
 
 int main()
   {
   isPrime();
   int n = v.size();
   long long sum = 0;
   for(int i = 0 ; i  n ; i ++)
{
   int k = v[i]-1;
   bool f = 0;
   for(int i = 1 ; i*i= k ; i++)
   if ( k % i == 0  prime[ i + ( k / i ) ] )  { 
 f=1 ; break ; }
 
   if ( !f ) sum += k;
}
   coutsumendl;
   }
 
 
 Regards
 Mukesh Tiwari


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project Euler Problem 357 in Haskell

2011-11-08 Thread Daniel Fischer
On Tuesday 08 November 2011, 14:54:18, Silvio Frischknecht wrote:
 On 11/08/2011 02:19 PM, Ryan Yates wrote:
  If I compile with optimizations:
  
  ghc --make -O3 primes.hs

So far, -O3 is not different from -O2 (-On gives you -O2 for n  2).

*Never* compile code you want to use without optimisations.

Compiling without optimisations is strictly for development, when 
compilation time matters because of frequent recompilation.
Once things have stabilised, compile them with optimisations only.

  
  I get an answer that is off by one from the C++ program in a few
  seconds.
 
 nice one. Though i wonder. The problem seems to be that without
 optimization sum is not tail-recursive. Is sum meant to not be
 tail-recursive?

Well, it is tail recursive (foldl, basically), but not strict.
So without optimisations you get the worst of boths worlds (tail recursion 
means no incremental output, as could be possible with foldr for lazy 
number types, not being strict in the accumulator means it builds huge 
thunks, like foldr with a function strict in the second argument).

 
 ghci sum [1..]
 
 eats up all the memory within seconds while
 
 ghci foldl' (+) 0 [1..]
 
 does not
 
 So Mukesh if you want your program to run without -Ox you should
 probably define your one sum'
 
 import Data.List
 sum' = foldl' (+) 0

That'd help, it would still be dog-slow, though, since optimisation is also 
crucial for the sieve.

 
 Silvio

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] zlib build failure on recent GHC

2011-11-07 Thread Daniel Fischer
On Monday 07 November 2011, 21:06:17, Jason Dagit wrote:
 On Mon, Nov 7, 2011 at 8:17 AM, Johan Tibell johan.tib...@gmail.com 
wrote:
  This is due to a change in how FFI imports and newtypes work. GHC was
  recently changed to not allow you to use newtypes in FFI imports
  unless the constructor of the newtype is in scope. This broke quite a
  few libraries. I have patched a few of them and I've sent a patch to
  the zlib maintainer.
 
 This seems like a big change.

But it introduces conformance with the report:

http://www.haskell.org/onlinereport/haskell2010/haskellch8.html#x15-1540008.4 
(sec. 8.4.2, Foreign Types)

Consequently, in order for a type defined by newtype to be used in a 
foreign declaration outside of the module that defines it, the type must 
not be exported abstractly.

Previous behaviour violated that, hence the change.

 Where should I be watching to know
 about this ahead of time?  I bet I have to fix some of my packages.
 
 Thanks,
 Jason

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install problem

2011-11-05 Thread Daniel Fischer
On Saturday 05 November 2011, 16:00:40, Ivan Lazar Miljenovic wrote:
 On 6 November 2011 01:52, Victor Miller victorsmil...@gmail.com wrote:
  Lately whenever I try to install a cabal package it fails with the
  following error message:
  
  Could not find module `Control.Monad.State':
  Perhaps you haven't installed the profiling libraries for
  package `mtl-2.0.1.0'?
  Use -v to see a list of the files searched for.
 
 That means that the package hasn't listed mtl as a dependency in its
 .cabal file.

Or it means that mtl wasn't built for profiling, but cabal tries to build 
the new package for profiling.
In that case, either don't try to build new packages for profiling, or 
reinstall mtl (and everything depending on it) also building the profiling 
libraries.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Ridiculously slow FFI, or cairo binding?

2011-11-02 Thread Daniel Fischer
On Wednesday 02 November 2011, 10:19:08, Eugene Kirpichov wrote:
 I forgot to specify my environment.
 
 Windows Server 2008 R2 x64, ghc 7.0.3.
 
 However, I observed the same speed differences on a 64-bit ubuntu with
 ghc 6.12 - I profiled my application with cairo-trace, and
 cairo-perf-trace drew in a fraction of a second the picture that my
 Haskell program spend a dozen seconds drawing.

Just FYI,

$ uname -a
Linux linux-v7dw.site 2.6.37.6-0.7-desktop #1 SMP PREEMPT 2011-07-21 
02:17:24 +0200 x86_64 x86_64 x86_64 GNU/Linux

$ g++ -O3 -o csurf surf.cc -I/usr/include/cairo -cairo
$ time ./csurf 

real0m0.126s
user0m0.119s
sys 0m0.006s
$ ghc-7.0.4 -O2 hssurf.hs 
[1 of 1] Compiling Main ( hssurf.hs, hssurf.o )
Linking hssurf ...
$ time ./hssurf 

real0m5.857s
user0m5.840s
sys 0m0.011s
$ ghc -O2 hssurf.hs -o hssurf2
[1 of 1] Compiling Main ( hssurf.hs, hssurf.o )
Linking hssurf2 ...
$ time ./hssurf2 

real0m0.355s
user0m0.350s
sys 0m0.005s

(fromRational . toRational) is still slow, but nowhere as slow as it used 
to be.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] When does the UNPACK pragma work?

2011-10-28 Thread Daniel Fischer
On Friday 28 October 2011, 11:41:15, Eugene Kirpichov wrote:
 newtype Day = ModifiedJulianDay {toModifiedJulianDay :: Integer}
 newtype DiffTime = MkDiffTime Pico
 
 And Pico is also essentially a newtype for Integer.
 
 So, I'm getting warnings on this definition of UTCTime.
 QUESTION: Is it the case that I can only UNPACK primitive fields, and
 not even their newtypes?

The problem is that you can't {-# UNPACK #-} Integer.
You can only unpack single-constructor types.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] When does the UNPACK pragma work?

2011-10-28 Thread Daniel Fischer
On Friday 28 October 2011, 11:57:54, Eugene Kirpichov wrote:
 Another question: Can I unpack some fields in a record and not unpack
 others?

Yes, no problem with that. 

 Does their order matter then?

In what way? The order of the fields in the definition of the type will 
determine the order in which the components (pointers/unpacked values) 
appear in the constructor. That may influence performance, but I wouldn't 
expect a significant difference.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Really impossible to reinstall `base' using cabal?

2011-10-26 Thread Daniel Fischer
On Wednesday 26 October 2011, 22:58:46, Joachim Breitner wrote:
 Hi,
 
 Am Mittwoch, den 26.10.2011, 13:10 +1100 schrieb Ivan Lazar Miljenovic:
   How did you get your ghc?
   If from your distro's package manager, you should be able to get the
   dyn- libs from that too.
  
  Unless you distro hasn't built GHC with dynamic library support.
 
 Debian (and in extension, Ubuntu) builds a ghc-dynamic package
 (http://packages.debian.org/sid/ghc-dynamic) on i386 and amd64, but does
 not build -dyn variants of the packaged libraries. So you base and
 everything that comes with ghc is covered, everything else (including
 stuff like mtl) is not.

But everything that doesn't come with ghc *can* be reinstalled (though one 
has to be careful, and it may be inconvenient), so you provide a good 
starting point.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Really impossible to reinstall `base' using cabal?

2011-10-25 Thread Daniel Fischer
On Tuesday 25 October 2011, 22:32:23, Captain Freako wrote:
 dbanas@dbanas-eeepc:~$ cabal install base
 
 and got this:
 
 Resolving dependencies...
 cabal: internal error: impossible
 
 Is it really impossible to use cabal to reinstall `base'?

Fortunately, yes. Reinstalling base is impossible (at least with GHC, might 
be possible with other compilers), so it's good that cabal doesn't even 
try.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Really impossible to reinstall `base' using cabal?

2011-10-25 Thread Daniel Fischer
On Wednesday 26 October 2011, 02:00:49, Captain Freako wrote:
 So, do you have any advice for me, with regard to solving this issue:
 
 Implicit import declaration:
Could not find module `Prelude':
  Perhaps you haven't installed the dyn libraries for package
 `base'?
 
 ?
 
 That is, how do I get the dynamic versions of the `base' package
 libraries installed, if not via a `cabal install'?

How did you get your ghc?
If from your distro's package manager, you should be able to get the dyn-
libs from that too.
If downloaded from the ghc page or built from source, well, then they 
should already be there, if they aren't, something went wrong.
Other methods?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error when installing RSA (for yesod) with GHC 7.2.1

2011-10-24 Thread Daniel Fischer
On Monday 24 October 2011, 23:13:32, Yves Parès wrote:
 I'm using GHC 7.2.1 and cabal-install 0.8 (Cabal 1.8.0.2), and when
 cabal install rsa

 
 Apparently it's an instance being declared twice.
 However RSA hackage page states that it compiles under GHC 7.2:
 http://hackage.haskell.org/package/RSA

The instance in the rsa package is guarded by a Cabal MIN_VERSION macro:
 
#if !MIN_VERSION_random(1,0,1)
instance Random Word8 where
  randomR (a,b) g = let aI::Int = fromIntegral a 
bI::Int = fromIntegral b
(x, g') = randomR (aI, bI) g
in (fromIntegral x, g')
  random  = randomR (minBound, maxBound)
#endif

Unfortunately, that macro was broken in some Cabal versions, among them 
1.8.0.2, so the negated check goes wrong (#if !(MIN_...) would work).
[As a quickfix for this package, you could edit the source, but you'll 
probably come across more macro problems later.]

Build yourself a new cabal-install.
If you use 7.2.1 for that, the recipe at https://gist.github.com/1169332 
tells you what you have to change.
If you have an older ghc still available, the vanilla procedure should work 
with that (if you're using the old 6.12.* with the Cabal-1.8.0.2, first 
install a later Cabal version, 1.8.0.6 works).

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] SpecConstr message while compiling

2011-10-23 Thread Daniel Fischer
On Sunday 23 October 2011, 19:33:55, Daniel Díaz Casanueva wrote:
 Hi, cafe!
 
 I wrote a program and had the following message while compiling (with
 -O2):
 
 SpecConstr
 Function `addOc{v s6RL} [lid]'
   has four call patterns, but the limit is 3
 Use -fspec-constr-count=n to set the bound
 Use -dppr-debug to see specialisations
 
 What it means? Is it bad? It only happens when compiling with -O2.

It's nothing serious.
It's just a message (that accidentally was output by default in the 7.0.* 
series) that the spec-constr pass could have done more specialising, but 
the limit forbade it.

More specialising on constructors means

- certainly bigger code
- potentially faster code

but it could also become slower (most likely because of worse cache 
locality).

It's not even a warning, just a notification.

 
 addOc is a local function (defined in a where clause). If it helps, here
 is the definition:
 
 addOc x [] = [(x,1)]
 addOc x ((y,n):ys) = if x == y then (y,n+1) : ys
else (y,n) : addOc x ys
 
 I want to know if there is something wrong or a I don't need to take
 care about this.

You need not take care of it, but you can try out and pass
-fspec-constr-count=N
on the command line (here, N = 4 is a good start) to see if the generated 
code is faster.

 
 Thanks in advance,
 Daniel Díaz.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hello Haskell

2011-10-23 Thread Daniel Fischer
On Monday 24 October 2011, 03:54:09, Erik de Castro Lopo wrote:
 R J wrote:
  hey Haskell this is nuts http://www.business10i.com
  hey Haskell this is nuts ://xxx.xxx.xxx
 
 Maybe its time to moderate all newcomers to this list, at least
 until they post one non-spam message to the list.

Just for the record, not a newcomer, and has non-spam messages, e.g.

http://www.haskell.org/pipermail/haskell-cafe/2010-May/077871.html
http://www.haskell.org/pipermail/haskell-cafe/2010-May/078054.html

 
 If you need volunteers to do this moderation I'll stick my hand up.
 
 Erik


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] hello Haskell

2011-10-23 Thread Daniel Fischer
On Monday 24 October 2011, 05:04:03, Erik de Castro Lopo wrote:
 That suggests a hijacked account.

Looks quite so, cf. Conrad Parker's message.

 Such accounts could still be put under moderation.

Yes, that's probably the best.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] haskell-janitors (was Re: New rss maintainer)

2011-10-23 Thread Daniel Fischer
On Monday 24 October 2011, 04:56:49, Erik de Castro Lopo wrote:
 Conrad Parker wrote:
  I like the janitors idea because it is practical, and I also like the
  ideal world where every package has an active maintainer.
  
  How about we set up the haskell-janitors github group as Vincent
 
  suggests, with some basic rules like:
 Just to make its intent more obvious, I would suggest the name
 haskell-pkg-janitors.

Emphatically seconded.

 
 Erik


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] runStateT execution times measurement baffling

2011-10-22 Thread Daniel Fischer
On Saturday 22 October 2011, 23:07:44, thomas burt wrote:
 Sorry, thought I had replied to this with my result!
 
 I added `seq` and $! inside `stuffToDo` to ensure that there weren't any
 thunks left around after it was called.
 
 The measured times were only a few hundredths of a second apart after
 that.
 
 So, apparently even with a strict StateT, partially evaluated references
 can easily be left around all the way until the call to runStateT
 returns.

Yes. The 'Strict' isn't very deep, it just means that on 'bind' (=), the 
state/value pair is evaluated to whnf. The components can easily contain 
unevaluated thunks. The strictness analyser (supposing you compile with 
optimisations) then can often see further and find that it's good to keep 
more things evaluated. It's easier for the strictness analyser than for the 
lazy variant (where the state/value pair is bound by a lazy pattern), but 
it still doesn't detect all opportunities for strict evaluation, so you're 
often enough left with accumulating unevaluated thunks.
(The compiler may only add strictness where it can prove that doesn't 
change the semantics of the programme, so the strictness analyser has a 
pretty hard job.)

 In this case my state is a record, if that makes any
 difference.

Well, it does, in comparison to simpler types. If the state is a plain Int, 
it's *relatively* easy to find out whether demanding the end result 
requires the evaluation of intermediate states. The more components and/or 
layers your state has, the harder it is to determine which ones of them are 
necessary to evaluate for the end result, the more opportunities for 
strictness will go unnoticed.
Strict fields in the record can greatly help then.

 It's not what I expected... I can see why my example is too
 small to show why it behaved this way though.
 
 I thought pattern matching (in Haskell98) was itself strict, so I don't

Yes, but that only means that the value is evaluated to the outermost 
constructor (or, in the case of nested patterns, as far as required). The 
constructor fields by default remain unevaluated (but they are now directly 
accessible thunks and no longer thunks hidden inside another thunk).

 see what the difference between a lazy and strict stateT is, except
 perhaps in cases that the value of runStateT is bound via a different
 mechanism than pattern matching.

The difference is that (=) in the strict StateT takes apart the 
state/value pair, creating two blobs and a constructor combing those to a 
pair, while (=) in the lazy StateT doesn't take apart the state/value 
blob. The latter makes it easier for thunks to accumulate (but on the other 
hand, it allows some feats that can't be done with the former, much less 
with even stricter variants).


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haddock fails on ConfigFile, but why?

2011-10-21 Thread Daniel Fischer
On Friday 21 October 2011, 23:49:45, Magnus Therning wrote:
 Would love to get some help on making Haddock accept ConfigFile[1]. The
 error message is about as far from helpful as you can get ;)
 
   dist/build/tmp-15743/src/Data/ConfigFile/Monadic.hs:34:1:
   parse error on input `import'
 
 The author is informed but is as confused as me, it seems[2].
 
 /M
 
 [1] http://hackage.haskell.org/package/ConfigFile
 [2] https://github.com/jgoerzen/configfile/issues/4

It may be that haddock requires the comments to be indented, or at least 
the bird-tracke code blocks.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haddock fails on ConfigFile, but why?

2011-10-21 Thread Daniel Fischer
On Friday 21 October 2011, 23:49:45, Magnus Therning wrote:
 Would love to get some help on making Haddock accept ConfigFile[1]. The
 error message is about as far from helpful as you can get ;)
 
   dist/build/tmp-15743/src/Data/ConfigFile/Monadic.hs:34:1:
   parse error on input `import'
 
 The author is informed but is as confused as me, it seems[2].

Okay, a bit of experimentation showed that the imports must come before the 
haddock comment section $overview.

Whether it's a haddock bug, or a feature request for haddock to handle such 
situations, I don't know.

Cheers,
Daniel



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correction: subclasses and classes with same type in instance

2011-10-16 Thread Daniel Fischer
On Sunday 16 October 2011, 20:03:02, Patrick Browne wrote:
 Hi,
 Does the subclass relation have any meaning when two classes
 have instances with the same type?
 I get the same results from Listing 1 and Listing 2 below.
 Regards,
 Pat

The only effect of a superclass constraint is that you can't make a type an 
instance of the subclass without a superclass instance for the type in 
scope.
Usually, a superclass constraint means there is a connection between the 
methods of both classes (like for Eq/Ord), and then it is expected that the 
instances respect that connection, but the compiler can't enforce that.

In your example, the only difference is that with the superclass constraint

foo :: House h = h - Integer
foo h = addressB h + addressH h

works, while without superclass constraint, foo would need both classes in 
its context.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Correction: subclasses and classes with same type in instance

2011-10-16 Thread Daniel Fischer
On Sunday 16 October 2011, 21:50:13, Patrick Browne wrote:
 In the current example does the following totally or partially ignore
 the type class system.
 boo :: Shed - Integer
 boo h = addressB h + addressH h

It doesn't ignore the type class system at all.
It's a monomorphic function using methods from the classes Building and 
House, so it just has to verify that Shed is an instance of both classes.
Without the superclass constraint on House, it's two unrelated lookups, 
with the superclass constraint, the compiler can choose to lookup both 
separately, or it could first determine that due to the superclass 
constraint, it needs only look up the House instance.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fwd: how to increase the stack size

2011-10-16 Thread Daniel Fischer
On Monday 17 October 2011, 04:39:49, kolli kolli wrote:
 when I am running the program in my terminal on ubuntu its showing me
 GHC stack-space overflow: current limit is 536870912 bytes.
 Use the `-Ksize' option to increase it.
  how can i increase the stack sizePlz help me out

$ ./yourProg +RTS -K32M -RTS args

to set the stack size to 32M; args are the command line arguments you want 
to pass to yourProg, if there are none, the -RTS isn't necessary.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] __GLASGOW_HASKELL__ macro in 7.2.1

2011-10-14 Thread Daniel Fischer
On Friday 14 October 2011, 16:47:45, JP Moresmau wrote:
 Hello list,
 I must be doing something stupid, but what?
 
 ghc --version
 The Glorious Glasgow Haskell Compilation System, version 7.2.1
 
 ghc -E -optP-dM -cpp Main.hs (per
 http://www.haskell.org/ghc/docs/latest/html/users_guide/options-phases.h
 tml)
 
 {-# LINE 1 Main.hs #-}
 #define mingw32_HOST_OS 1
 #define i386_BUILD_ARCH 1
 #define __GLASGOW_HASKELL__ 702
 #define __STDC_HOSTED__ 1
 #define i386_HOST_ARCH 1
 #define mingw32_BUILD_OS 1
 
 I'm on Windows so everything else is correct except the line that
 tells me I'm using 7.0.2.

No, __GLASGOW_HASKELL__ == 702 means you're using ghc-7.2.*, not 7.0.2.

The second and third digit of the version are for the second component, so 
610 was 6.10.*, 612 was 6.12.*

 Unfortunately I have code that works under 7.0.3 and breaks under
 7.2.1 (and the 7.2.1 code breaks under 7.0.3, of course) so I don't
 see anything other option than conditional compilation.

#in __GLASGOW_HASKELL__ = 702
-- code for 7.2.1 and greater
#else
-- code for ghc = 7.0.4
#endif



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lists concatenation being O(n)

2011-10-14 Thread Daniel Fischer
On Friday 14 October 2011, 16:55:14, Bas van Dijk wrote:
 On 13 October 2011 20:53, Albert Y. C. Lai tre...@vex.net wrote:
  The number of new cons cells created in due course is Θ(length xs).
 
 I was actually surprised by this because I expected: length(xs++ys) to
 fuse into one efficient loop which doesn't create cons cells at all.
 
 Unfortunately, I was mistaken since length is defined recursively.
 
 length :: [a] - Int
 length l =  len l 0#
   where
 len :: [a] - Int# - Int
 len [] a# = I# a#
 len (_:xs) a# = len xs (a# +# 1#)
 
 However, if we would define it as:
 
 length = foldl' (l _ - l+1) 0
 
 And implemented foldl' using foldr as described here:
 
 http://www.haskell.org/pipermail/libraries/2011-October/016895.html
 
 then fuse = length(xs++ys) where for example xs = replicate 100 1
 and ys = replicate 5000 (1::Int) would compile to the following
 totally fused core:
 
 fuse :: Int
 fuse = case $wxs 100 0 of ww_srS {
  __DEFAULT - I# ww_srS
}
 
 $wxs :: Int# - Int# - Int#
 $wxs = \ (w_srL :: Int#) (ww_srO :: Int#) -
 case =# w_srL 1 of _ {
   False - $wxs (-# w_srL 1) (+# ww_srO 1);
   True  - $wxs1_rs8 5000 (+# ww_srO 1)
 }
 
 $wxs1_rs8 :: Int# - Int# - Int#
 $wxs1_rs8 =
   \ (w_srA :: Int#) (ww_srD :: Int#) -
 case =# w_srA 1 of _ {
   False - $wxs1_rs8 (-# w_srA 1) (+# ww_srD 1);
   True  - +# ww_srD 1
 }

Yes, that's wonderful, but it's not so wonderful for types more complicated 
than Int.

Integer is evil enough: With 

fuse = length ([1 .. 5000] ++ [0 .. 6000])

Prelude Fuse fuse
Heap exhausted;
Current maximum heap size is 1258291200 bytes (1200 MB);
use `+RTS -Msize' to increase it.

The current length has no problems:

Prelude length ([1 .. 5000] ++ [0 .. 6000])
11001
(2.55 secs, 11609850632 bytes)

Before foldl('), sum, length can be implemented in terms of foldr to get 
fusion, a lot has to be done still.
Currently you'd get an improvement in some cases for a catastrophic 
behaviour in many others.

Cheers,
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Lists concatenation being O(n)

2011-10-14 Thread Daniel Fischer
On Friday 14 October 2011, 17:10:00, Yves Parès wrote:
 Wow, I don't get core haskell, but I get you point.
 It's indeed odd foldl' doesn't use foldr (and sum doesn't use foldl'
 instead of foldl as (+) is strict (*)) if foldr permits loop fusion.

No, it's not odd. The fusion technology isn't yet capable of handling 
everything you throw at it, and you get catastrophically bad results if it 
fails.
With the current implementation, you pay a (significant) price at the 
points where fusion would succeed but have good enough worst-case 
behaviour.

 
 (*) Anyway, is there a place where foldl is preferable over foldl' ?
 Never happened to me, I always use right-folding if I want lazy
 evaluation, to benefit from guarded recursion.

Bas quoted and linked the Foldr Foldl Foldl' page and referred to the 
example. As the author of that example, I know that it is an artificial 
example; I thought it up to answer the question when would foldl be better 
than foldl'?. I have never come across such a situation in real life.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Implementing a new primtype

2011-10-10 Thread Daniel Fischer
On Tuesday 11 October 2011, 00:57:39, Paul Monday wrote:
 There seems to be plenty of documentation around on implementing a new
 primop, much of it needs some tweaking as files have moved and such.  I
 can't seem to find any documentation about how to implement primtypes
 though.
 
 For example, I want to experiment with a new primtype DV#, my
 assumption that the type was first declared in the primops.txt.pp seems
 incorrect.  So I'm trying to backtrack a bit and see where primtypes
 first appear, I'm hoping someone can at least give me a pointer :-)
 
 For example:
 ./compiler/prelude/primops.txt.pp
 
 Add the following:
 primtype DoubleVec# a

Has a type parameter

 
 Compiles fine
 
 Add a primop on the type:
 primop ExtractDoubleVecOp extractDoubleVec# GenPrimOp
DoubleVec# - Int# - Double#

Used without type parameter

Might be as simple as that.

 genprimopcode: ppType: can't handle: TyApp DoubleVec# []


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Best bit LIST data structure

2011-10-09 Thread Daniel Fischer
On Sunday 09 October 2011, 15:54:14, Joachim Breitner wrote:
 Hi,
 
 Am Freitag, den 07.10.2011, 10:52 -0400 schrieb Ryan Newton:
  What about just using the Data.Bits instance of Integer?  Well,
  presently, the setBit instance for very large integers creates a whole
  new integer, shifts, and xors:
  
  http://haskell.org/ghc/docs/latest/html/libraries/base/src/Data-Bits.h
  tml#setBit (I don't know if it's possible to do better.  From quick
  googling GMP seems to use an array of limbs rather than a chunked
  list, so maybe there's no way to treat large Integers as a list and
  update only the front...)
 
 interesting idea. Should this be considered a bug in ghc? (Not that it
 cannot represent the result, but that it crashes even out of ghci):
 
 $ ghci
 GHCi, version 7.0.4: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer-gmp ... linking ... done.
 Loading package base ... linking ... done.
 Prelude :m + Data.Bits
 Prelude Data.Bits setBit 0 (2^63-1::Int)
 gmp: overflow in mpz type
 Abgebrochen

says info gmp:

  `_mp_size' and `_mp_alloc' are `int', although `mp_size_t' is
usually a `long'.  This is done to make the fields just 32 bits on some
64 bits systems, thereby saving a few bytes of data space but still
providing plenty of range.

So it seems to be GMP itself.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to install haddock with ghc-7.2.1?

2011-10-06 Thread Daniel Fischer
On Thursday 06 October 2011, 15:20:44, Paulo Pocinho wrote:
 Implicit import declaration:
 base:Prelude can't be safely imported! The package (base) the
 module resides in isn't trusted.

Due to an oversight, the base package isn't trusted by default in 
ghc-7.2.1, run

C:\ ghc-pkg trust base

to trust it.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] module - package

2011-09-30 Thread Daniel Fischer
On Friday 30 September 2011, 21:04:48, Roman Beslik wrote:
 Hello. How can I find which installed package a specified module belongs
 to? ghci or cabal or ghc-pkg?

$ ghc-pkg find-module Foo.Bar.Baz


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-25 Thread Daniel Fischer
On Sunday 25 September 2011, 19:20:52, Chris Smith wrote:
 Would it be an accurate summary of this thread that people are asking
 for (not including quibbles about naming and a few types):

Not quite, I'm afraid.

 
 class Ord a = Enum a where
 succ :: a - a
 pred :: a - a
 fromEnum :: a - Int(eger)
 toEnum :: Int(eger) - a
 -- No instance for Float/Double

I'm not in favour of introducing an Ord constraint here.
For

data WeekDay
= Sunday
...

data Month
= January
...

an Ord instance would be dubious, but Enum is plenty fine.

 
 class Ord a = Range a where
 rangeFromTo :: a - a - [a] -- subsumes Ix.range / Enum.enumFromTo
 rangeFromThenTo :: a - a - a - [a]
 inRange   :: (a, a) - a - Bool
 -- Does have instances for Float/Double.  List ranges desugar to this.
 -- Also has instances for tuples

Don't mix range and arithmetic sequences. I want arithmetic sequences for 
Double, Float and Rational, but not range.
(For Float and Double one could implement range [all values between the 
given bounds, in increasing order, would be the desired/expected semantics 
for that, I think?], but I'm rather sure that's not what one does normally 
want, and for Rational, you can't even implement it.)

Also, I doubt whether rangeFromThenTo is a useful addition to range, I 
don't see how it would be natural for tuples. (The Ix instance for tuples 
doesn't use the lexicographic ordering, but the box-partial order - 
presumably so would the Range instance, so the 'distance' between two 
tuples would depend on the given bounds. Using the box-partial order is 
fine for range, but seems weird for blahFromThenTo.)

 
 class Range a = InfiniteRange a where -- [1]
 rangeFrom :: a - [a]
 rangeFromThen :: a - a - [a]
 -- Has instances for Float/Double
 -- No instances for tuples
 
 class Range a = Ix a where
 index :: (a, a) - a - Int
 rangeSize :: (a, a) - Int
 
 -- Again no instances for Float/Double.  Having an instance here implies
 -- that the rangeFrom* are complete, containing all 'inRange' values

Ho Hum. So Range would continue the same ambiguity/confusion that started 
this thread, albeit in mitigated form.

Separating range from arithmetic (or 'fixed-step-size') sequences is 
cleaner (we'd lose default methods anyway, you need Enum or Num  Ord for 
them, but we now have numericEnumFrom* to make Enum instances for Num types 
easier, we could move the current default methods out of the class to have 
enumEnumFrom* so that writing instances for Enum types would be easier).

 
 class (RealFrac a, Floating a) = RealFloat a where
 ... -- existing stuff
 (..), (.=.), (..), (.=.), (.==.) :: a - a - Bool
 -- these are IEEE semantics when applicable
 
 instance Ord Float where ... -- real Ord instance where NaN has a place

Yes. I have pondered leaving Eq and Ord for Double and Float as is and 
providing a newtype wrapper with container/sort-safe instances, but that'd 
be cumbersome, people wouldn't know they exist and (when) they have to use 
them, urk.
Also, although it's a change in behaviour, it doesn't badly break backwards 
compatibility., as far as I can see (I hope x /= x isn't heavily used as a 
NaN test).
So yes, definitely yes.

 
 There would be the obvious properties stated for types that are
 instances of both Enum and Range, but this allows for non-Enum types to
 still be Range instances.
 
 If there's general agreement on this, then we at least have a proposal,
 and one that doesn't massively complicate the existing system.  The next
 step, I suppose would be to implement it in an AltPrelude module and
 (sadly, since Enum is changing meaning) a trivial GHC language
 extension.  Then the real hard work of convincing more people to use it
 would start.  If that succeeds, the next hard work would be finding a
 compatible way to make the transition...
 
 I'm not happy with InfiniteRange, but I imagine the alternative (runtime
 errors) won't be popular in the present crowd.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-25 Thread Daniel Fischer
On Sunday 25 September 2011, 23:13:47, Chris Smith wrote:
  Don't mix range and arithmetic sequences. I want arithmetic sequences
  for Double, Float and Rational, but not range.
  (For Float and Double one could implement range [all values between
  the given bounds, in increasing order, would be the desired/expected
  semantics for that, I think?],
 
 Okay, fine, I tried.  Obviously, I'm opposed to just flat removing
 features from the language, especially when they are so useful that they
 are being used without any difficulty at all by the 12 year olds I'm
 teaching right now.

Agreed. But If we want a change to remove a wart, we should try to remove 
it completely. We can still settle for make it smaller if it doesn't work 
out.

 
 Someone (sorry, not me) should really write up the proposed change to
 Ord for Float/Double

Okay.

 and shepherd them through the haskell-prime process.

Uh oh. I ope that can be done with a libraries proposal.
(Ian says yes :-D)

 That one shouldn't even be controversial; there's already an
 isNaN people should be using for NaN checks, and any code relying on the
 current behavior is for all intents and purposes broken anyway.  The
 only question is whether to add the new methods to RealFloat (breaking
 on the bizarre off chance that someone has written a nonstandard
 RealFloat instance), or add a new IEEE type class.

Add to RealFloat, default to the Eq/Ord functions, I'd say.

But that's not the only question. Is -0.0 == 0.0 or not?
I lean towards no because of 1/x, but I'm not wedded to that.

And: distinguish NaNs or identify them all?
I lean towards identifying them all, I've never cared for whether they come 
from 0/0, Infinity - Infinity or what, but I could be convinced.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] A Missing Issue on Second Generation Strategies

2011-09-24 Thread Daniel Fischer
On Saturday 24 September 2011, 18:01:10, Burak Ekici wrote:
 Dear List,
 
 I am trying to parallelize RSA encryption and decryption by using below
 manner, but when I run executable output file with +RTS -s -N2
 command on Windows 7, output stats say 4 sparks are being created
 however none of them converted into real OS threads.
 
 -- SPARKS :4 (0 converted, 4 pruned) --
 
 I was thinking that the problem could occur due to lack of forcing
 parallelization but, as far as I know 'rdeepseq' works for that aim.
 
 Briefly, I could not solve the issue why parallelization was not being
 implemented. I would be appreciated if any of you shed a light on the
 issue that I missed.
 
 Here is the mentioned part of code:
 
 split4ToEnc :: RSAPublicKey - [Integer] - [Integer]
 split4ToEnc (PUB n e) [] = []
 split4ToEnc (PUB n e) (x:xs) =
  ((ersa (PUB n e) secondPart2) ++ (ersa (PUB n e) secondPart1) ++ (ersa
 (PUB n e) firstPart2) ++ (ersa (PUB n e) firstPart1)) `using` strategy
 where
   firstPart1  = fst (Main.splitAt((length (x:xs)) `div` 4)
 (fst(Main.splitAt ((length (x:xs)) `div` 2) (x:xs firstPart2  = snd
 (Main.splitAt((length (x:xs)) `div` 4) (fst(Main.splitAt ((length
 (x:xs)) `div` 2) (x:xs secondPart1  = fst (Main.splitAt((length
 (x:xs)) `div` 4) (snd(Main.splitAt ((length (x:xs)) `div` 2) (x:xs
 secondPart2  = snd (Main.splitAt((length (x:xs)) `div` 4)
 (snd(Main.splitAt ((length (x:xs)) `div` 2) (x:xs strategy res = do
   a - rpar (ersa (PUB n e) (firstPart1) `using`
 rdeepseq) b - rpar (ersa (PUB n e) (firstPart2) `using` rdeepseq) c -
 rpar (ersa (PUB n e) (secondPart1) `using` rdeepseq) d - rpar (ersa
 (PUB n e) (secondPart2) `using` rdeepseq) rdeepseq res

First, you are doing a lot of unnecessary recalculation, calculate the 
length once and reuse it, also the parts of input and output lists.
If you don't give a name to the parts of your result, the strategy looks 
completely unrelated to the result to the compiler, hence no gain (if 
you're unlucky, they might be computed twice).

split4ToEnc key [] = []
split4ToEnc key xs = d' ++ c' ++ b' ++ a'
 -- don't need (x:xs), after matching [] failed that's the only possibility
 -- and the first element isn't used
  where
len = length xs
(firstHalf,secondHalf) = splitAt (len `quot` 2) xs
(firstPart1,firstPart2) = splitAt (len `quot` 4) firstHalf
(secondPart1,secondPart2) = splitAt (len `quot` 4) secondHalf
a = ersa key firstPart1
b = ersa key firstPart2
c = ersa key secondPart1
d = ersa key secondPart2
(a',b',c',d') 
  = (a,b,c,d) `using` parTuple4 rdeepseq rdeepseq rdeepseq rdeepseq

should give you some parallelism. People familiar with the topic can 
probably suggest better strategies.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] stack overflow pain

2011-09-21 Thread Daniel Fischer
On Thursday 22 September 2011, 01:00:37, Tim Docker wrote: 
 I believe the error is happening in the concat because there are
 subsequent IO actions that fail to execute. ie the code is equivalent
 to:
 
  vs - fmap concat $ mapM applyAction sas
  someOtherAction
  consume vs
 
 and someOtherAction seems not to be run. However, to be sure, I'll
 confirm with code akin to what you suggest above.

I suspect that `applyAction x' produces a large thunk for several x in sas, 
and those blow the stack.

You could try forcing evaluation earlier,

mapM' :: (a - IO [b]) - [a] - IO [b]
mapM' act (m:ms) = do
xs - act m
yss - length xs `seq` mapM' act ms
return (xs ++ yss)
mapM' _ [] = return []

perhaps even forcing the values of xs (deepseq, if b is an NFData 
instance).
Depending on what your actual problem is, that could help or make it worse.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-21 Thread Daniel Fischer
On Wednesday 21 September 2011, 20:39:09, Casey McCann wrote:
 On Wed, Sep 21, 2011 at 12:09 AM, Daniel Fischer
 
 daniel.is.fisc...@googlemail.com wrote:
  Yes. Which can be inconvenient if you are interested in whether you
  got a -0.0, so if that's the case, you can't simply use (== -0.0).
  Okay, problematic is a too strong word, but it's another case that may
  require special treatment.
 
 Hmm. I was going to suggest that it's not a major concern so long as
 the distinction can't be observed without using functions specific to
 floating point values, since that preserves consistent behavior for
 polymorphic functions, but... that's not true, because the sign is
 preserved when dividing by zero! So we currently have the following
 behavior:
 
 0   == (-0) = True
 1/0 == 1/(-0)   = False
 signum (-0) = 0.0
 signum (1/0)= 1.0
 signum (1/(-0)) = -1.0
 
 All of which is, I believe, completely correct according to IEEE
 semantics,

Yup.

 but seems to cause very awkward problems for any sensible
 semantics of Haskell's type classes.

Well, that's something you risk whenever you have an Eq instance regarding 
some non-identical values as equal. Some function may distinguish between 
them, cf. e.g. showTree in Data.Set/Map for a non-floating-point example.

 
 ...sigh.
 
  which is correct and shouldn't break any expected behavior.
  I don't think it's required that distinguishable values be unequal,
  
  But desirable, IMO.
 
 I'm ambivalent. I can see it making sense for truly equivalent values,
 where there's a reasonable expectation that anything using them should
 give the same answer, or when there's a clearly-defined normal form
 that values may be reduced to.

Yes, it's not an absolute, but if your Eq instance declares distinguishable 
values equal, you better have a very good reason for it.
The reason for Data.Set/Map is good enough, I think. -0.0 == 0.0 is 
borderline. If Double/Float get Eq and Ord instances avoiding the NaN 
poison, I'd prefer to distinguish -0.0 from 0.0 too, leaving the 
identification to the IEEE comparisons.

 
 But as demonstrated above, this isn't the case with signed zeros if
 Num is available as well as Eq.
 
  I still don't see why it makes sense to add separate IEEE comparisons
  
  Pure and simple: speed.
  That is what the machine instructions, and hence the primops, deliver.
 
 Oh, I assume the IEEE operations would be available no matter what,
 possibly as separate operations monomorphic to Float and Double, that

That too, but I want to keep the polymorphic variants available, it's 
easier to change a few type signatures near the top than hunting through 
the entire project to replace eqDouble with eqFloat etc. and recompile 
everything.

 they'd be used to define the partial ordering instance, and could be
 imported directly from some appropriate module.
 
 But as it turns out the partial ordering isn't valid anyway, so I
 retract this whole line of argument.
 
  Ah, yes, wherein someone suggested that comparing to NaN should be a
  runtime error rather than give incorrect results. A strictly more
  correct approach, but not one I find satisfactory...
  
  Umm, 'more correct' only in some sense. Definitely unsatisfactory.
 
 More correct in the very narrow sense of producing fewer incorrect
 answers, according to Haskell semantics. :] That it would produce
 fewer answers in general and a great deal more bottoms is another
 matter. Certainly not useful, and in fact actively counterproductive
 given that the whole purpose of silent NaNs is to allow computations
 to proceed without handling exceptions at every step along the way.

Quite.

 
 I'm becoming increasingly convinced that the only strictly coherent
 approach in the overall scheme of things would be to banish floating
 point values from most of the standard libraries except where they can

Hmm. I don't particularly like that idea. Correctly handling floating point 
numbers isn't trivial - So What? They're extremely useful, they deserve 
their place. Put a bumper over the sharpest edges, write Enter at your own 
risk on the garage door, that's enough.

 be given correct implementations according to Haskell semantics, and
 instead provide a module (not re-exported by the Prelude) that gives
 operations using precise IEEE semantics and access to all the expected
 primops and such. As you said above, the importance of floating point
 values is for speed, and the IEEE semantics are designed to support
 that. So I'm happy to consider floats as purely a performance
 optimization that should only be used when number crunching is
 actually a bottleneck.

 Let Rational be the default fractional type
 instead and save everyone a bunch of headaches.

If only things were so easy.
You can't satisfactorily define functions like sqrt, exp, log, sin, cos ...
for Rational, so for a large class of tasks you need floating point numbers 
(yes, one could also use arbitrary precision numbers

Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-20 Thread Daniel Fischer
On Tuesday 20 September 2011, 17:39:49, Ketil Malde wrote:
 Chris Smith cdsm...@gmail.com writes:
  It would be a shame if we lost an occasionally useful and easy to read
 
 You forgot confusing?  Expecting Enum to enumerate all inhabitants of
 a type seems very reasonable to me, and seems to hold for all
 non-floating point types.

And Rational (more generally, Ratio a). (Why does everybody forget that?)
Enumerating all inhabitants of a type (within some range) is only possible 
if there are well-defined successors and predecessors (modulo bounds).
For Double and Float, there are (excepting NaNs), so it could be done, but 
arguably that would be *far less* useful than the current instances.
For Rational, no such luck.

 A numeric range [a..a+n] might be expected
 to have a+n+1 elements, but that doesn't hold either for Float and
 Double.  I think Enum for floating point values is broken

Yes, it is. Like Eq and Ord.

 - but it is reality, so we need to deal with it.

Like Eq and Ord, it's just too damn convenient to have it.
So much nicer to write [0, 0.25 .. 1000] instead of
numericEnumFromThenTo 0 0.25 1000
and (x /= y) instead of
doublesDifferentOrNaN x y

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-20 Thread Daniel Fischer
On Tuesday 20 September 2011, 23:56:53, Evan Laforge wrote:
  I actually think the brokenness of Ord for floating point values is
  worse in many ways, as demonstrated by the ability to insert a value
  into a Data.Set.Set and have other values disappear from the set as
  a result. Getting an unexpected element in a list doesn't really seem
  as bad as silently corrupting entire data structures.
 
 Whoah, that's scary.  What are some examples of this happening?  Does
 this mean it's unsafe to store Doubles in a Map?

Too lazy to work out the details, but since
NaN ? x = False
for ? any of , , =, =, (==, /=) and compare is defined on terms of 
these, all results of compare involving a NaN are GT.
member and insert in Data.set use compare to find out where to go, so 
inserting NaNs puts them at the max position. Insert a couple, and 
rebalancing can put one above non-NaN values, oops.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-20 Thread Daniel Fischer
On Wednesday 21 September 2011, 00:20:09, Casey McCann wrote:
 This plays havoc with the search tree used internally by Set and Map,
 the result being that if you have any NaN values in the data
 structure, you may not be able to find other values anymore. Because
 NaN values never compare equal to themselves, I'm not sure if it's
 even possible to remove them from the structure,

filter (not . isNaN)

resp.

filterWithKey (\k _ - not $ isNaN k)

 and because of tree
 rebalancing I'm not sure how to predict what the impact of one or more
 NaNs would be over multiple operations on the data structure.

Yuck. Don't even try to predict that (unless you absolutely have to).

 
 In short: Using Doubles in a Set, or as the key to a Map, should be
 regarded as a bug until proven otherwise (i.e., proving that NaN will
 never be inserted).
 
 If you'd like to see an explicit demonstration (which you can try in
 GHCi yourself!) see here:
 http://stackoverflow.com/questions/6399648/what-happens-to-you-if-you-br
 eak-the-monad-laws/6399798#6399798 where I use it as an example of why
 it's important for type class instances to obey the relevant laws.

Nice and short.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-20 Thread Daniel Fischer
On Wednesday 21 September 2011, 00:38:12, Maciej Marcin Piechotka wrote:
 +1 for:
 
 class Eq a = Iq a where
 (.) :: a - a - Bool
 (.) :: a - a - Bool
 
 Regards

-1 for the class name, too easy to miscount the Es.

And perhaps it would be better to add the IEEE compliant(?) comparisons to 
the RealFloat class.

class (RealFrac a, Floating a) = RealFloat a where
...-- lots of stuff we already have
(==.) :: a - a - Bool
(.) :: a - a - Bool
...

However, I don't particularly like adding just a dot, that's too easily 
overlooked. On the other hand, I don't have a compelling idea either. 
(.==.), (..) would at least double the chances to spot the difference.

Anyway, +1 for an Ord instance with a total order (consistent with the 
natural order where applicable) and putting the IEEE comparisons somewhere 
else.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-20 Thread Daniel Fischer
On Wednesday 21 September 2011, 01:23:48, Casey McCann wrote:
 On Tue, Sep 20, 2011 at 6:58 PM, Daniel Fischer
 
 daniel.is.fisc...@googlemail.com wrote:
  On Wednesday 21 September 2011, 00:20:09, Casey McCann wrote:
  Because
  NaN values never compare equal to themselves, I'm not sure if it's
  even possible to remove them from the structure,
  
  filter (not . isNaN)
  
  resp.
  
  filterWithKey (\k _ - not $ isNaN k)
 
 Er, right. Yes, of course. I'm not sure what I was thinking there. :]
 Though that still leaves the question of any damage done in the
 meantime, unless the filtering would repair the tree in the process.

With fromList . Prelude.filter (not . isNaN) . toList and the corresponding 
for Maps, you'll get a valid NaN-less tree.
However, damage done in the meantime generally couldn't be undone.

 
  and because of tree
  rebalancing I'm not sure how to predict what the impact of one or
  more NaNs would be over multiple operations on the data structure.
  
  Yuck. Don't even try to predict that (unless you absolutely have to).
 
 Agreed. The consequence of not trying, however, is that it isn't
 viable to let things slide at all--every insertion must be checked for
 NaNs, because otherwise you lose any guarantee that the tree will be
 valid next time you use it.

Yes, where NaNs matter, you always have to check (well, unless you *know* 
that your calculations don't produce any NaNs).
Btw, -0.0 can be problematic too.

 
 One can imagine a similar data structure designed to be resilient and
 predictable in the face of ill-behaved comparisons, but surely it
 would be easier to just fix the problem instances!

Except that people might expect IEEE semantics for (==), () etc.
However, nowadays I tend to think that making the Eq and Ord instances 
well-behaved (wrt the class contract) and having separate IEEE comparisons 
would overall be preferable.
There is still the question whether all NaNs should be considered equal or 
not [and where Ord should place NaNs].

 
  If you'd like to see an explicit demonstration (which you can try in
  GHCi yourself!) see here:
  http://stackoverflow.com/questions/6399648/what-happens-to-you-if-you
  -br eak-the-monad-laws/6399798#6399798 where I use it as an example
  of why it's important for type class instances to obey the relevant
  laws.
  
  Nice and short.
 
 Yes, and credit where due for the original example. :] Don't recall
 which -cafe thread that came from, though.

Google suggests Exception for NaN from May.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] instance Enum Double considered not entirely great?

2011-09-20 Thread Daniel Fischer
On Wednesday 21 September 2011, 04:18:38, Casey McCann wrote:
 On Tue, Sep 20, 2011 at 8:20 PM, Daniel Fischer
 
 daniel.is.fisc...@googlemail.com wrote:
  Yes, where NaNs matter, you always have to check (well, unless you
  *know* that your calculations don't produce any NaNs).
  Btw, -0.0 can be problematic too.
 
 How so? As far as I can tell Ord and Eq treat it as equal to 0.0 in
 every way,

Yes. Which can be inconvenient if you are interested in whether you got a 
-0.0, so if that's the case, you can't simply use (== -0.0).
Okay, problematic is a too strong word, but it's another case that may 
require special treatment.

 which is correct and shouldn't break any expected behavior.
 I don't think it's required that distinguishable values be unequal,

But desirable, IMO.

 and while I imagine arguments could be made both ways on whether that
 would be a good idea, I don't see any way that could cause problems in
 code polymorphic on instances of Eq or Ord,

It wouldn't do that, as far as I'm aware.

 which is the main concern to my mind.
 
  Except that people might expect IEEE semantics for (==), () etc.
 
 Yes, but probably fewer people than expect Map and Set to work
 correctly. :]

True.

  However, nowadays I tend to think that making the Eq and Ord instances
  well-behaved (wrt the class contract) and having separate IEEE
  comparisons would overall be preferable.
  There is still the question whether all NaNs should be considered
  equal or not [and where Ord should place NaNs].
 
 IEEE semantics are incompatible with Ord regardless. The problem can
 be fixed by changing Ord, removing the instance completely, or
 changing the instance to ignore the IEEE spec. I think the latter is
 the least bad option in the big picture.

Agreed.

 
 I still don't see why it makes sense to add separate IEEE comparisons

Pure and simple: speed.
That is what the machine instructions, and hence the primops, deliver.

 instead of just adding a standard partial order class, though. Surely
 posets are common enough to justify the abstraction, and it surprises
 me that one isn't already included. No doubt there are at least three
 or four different partial ordering classes on Hackage already.
 
 As for where Ord should place NaN, I still suggest it be the least
 element, to be consistent with the Ord instance for Maybe.

Seems reasonable.

 If different NaNs are unequal, that may change matters.

Yeah, if there are a lot of them, it might be better to put them at the end 
[that is, make them larger than any non-NaN].

 
  Google suggests Exception for NaN from May.
 
 Ah, yes, wherein someone suggested that comparing to NaN should be a
 runtime error rather than give incorrect results. A strictly more
 correct approach, but not one I find satisfactory...

Umm, 'more correct' only in some sense. Definitely unsatisfactory.

do x - someList
   y - someComputation
   guard (not $ isNaN y)
   z - someOtherComputation
   return (if z  3 then foo z else bar z)


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The applicative instances for Either?

2011-09-17 Thread Daniel Fischer
On Saturday 17 September 2011, 08:42:42, Ketil Malde wrote:
 Hi,
 
 I have a program that makes use of the applicative instance for Either
 String.  I used to define these instances locally, but at some point,
 they became part of Control.Applicative.  I have limited the
 dependencies to 'base = 4', but apparently, some version 4s of base
 include this instance, some do not, and it causes problems for people
 trying to compile the program.
 
 Is there any information, or otherwise accessible source specifying
 exactly when this was changed,

Commited on 18th June 2010 to HEAD ;)
Checking the sources, it wasn't in base-4.2.0.2 (ghc-6.12.3), but it was in 
base-4.3.1.0 (ghc-7.0.2), so it was introduced with base-4.3

 so that I can have more precise
 dependencies?  And is there a simple way to handle this conditionally,
 either within cabal, or using CPP?

Simplest way would be CPP, I think. Cabal provides a MIN_VERSION_foo macro, 
so

-- The extra parentheses might be necessary, some Cabal version(s)
-- had a buggy MIN_VERSION macro, I don't remember the details

#if  !(MIN_VERSION_base(4,3,0))
instance Applicative (Either e) where
...
#endif

You can have a flag based on which the version of the module with or 
without the instance is imported, but the above seems much simpler



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error in Installing Data.deriveTH

2011-09-17 Thread Daniel Fischer
On Saturday 17 September 2011, 12:41:17, mukesh tiwari wrote:
 
  Does there exist an unversioned ghc? What does
  
  $ which ghc
  
  print?
 
  It prints nothing .

Okay, since cabal defaults to looking for plain ghc when no compiler is 
explicitly passed, that explains why it didn't work without --with-compiler

Normally, when ghc is installed, it creates versionless symlinks to the 
actual scripts/binaries, so there should be symbolic links

ghc, ghci, ghc-pkg

to the versioned things (and haddock-haddock-ghc-7.2.1, 
runhaskell-runghc), many programmes expect unversioned tools by default.

It might be that your install is broken, but probably creating the symlinks 
yourself (read the ln man-page and be careful when you create them) will be 
enough.

 
 ntro@ntro-HP-dx2480-MT-NA121PA:/usr/local/bin$ ls ghc*
 ghc-7.2.1  ghci-7.2.1  ghc-pkg-7.2.1

Those should be linked to.

 
 ntro@ntro-HP-dx2480-MT-NA121PA:/usr/local/bin$ ls
 django-admin.py  eggy   eric4-compareeric4-doc
 eric4-pluginrepository  eric4-re  eric4-trpreviewer
 eric4-webbrowser  ghc-pkg-7.2.1  hp2ps   runghc  spyder
 Editra   eric4  eric4-configure  eric4-editor
 eric4-pluginuninstall   eric4-sqlbrowser  eric4-uipreviewer
 ghc-7.2.1 haddockhpc runhaskell  UTscapy
 Editra.pyw   eric4-api  eric4-diff   eric4-plugininstall
 eric4-qregexp   eric4-trayeric4-unittest
 ghci-7.2.1haddock-ghc-7.2.1  hsc2hs  scapy
 
 So should i delete ghc-6.12.1 from /var/lib

Optional. It shouldn't cause any problems (unless you need the space).

 and move the ghc-7.2.1 from
 /usr/local/lib to /var/lib to execute cabal install pkg-name -v
 --dry-run ?

No, leave /usr/local/lib where it is, moving it would cause massive 
breakage. For example, /usr/bin/ghc-7.2.1 expects the libraries and 
binaries there.

The only problem was that cabal looked for ghc which no longer exists on 
your path. That fact is somewhat dubious, as normally installing ghc 
creates the symlinks, but creating them is probably all that's needed if 
invoking ghc-7.2.1 works.

 As /usr/local/bin is already in the path i don't need to
 move any files from here. Am i correct  ?

Don't move anything. If your ghc-7.2.1 is broken, you will need to 
reinstall (that or another version), otherwise you can work with always 
using (and passing) the explicit version or, more conveniently, create the 
expected symlinks.

Cheers,
Daniel


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error in Installing Data.deriveTH

2011-09-16 Thread Daniel Fischer
On Friday 16 September 2011, 13:55:25, mukesh tiwari wrote:
 Thank you for reply Daniel . I installed the ghc-7.2.1 but now running
 cabal install keys  --dry-run -v gives error. One more thing i would
 like to know. Before installing any package , i should check its
 dependency and if it depends on any global namespace package
 [/usr/local/lib/ghc-7.2.1/package .conf.d ] so i should not install the
 global namespace package using cabal install global-package

That depends on what you have in the global db, but it's a good rule of 
thumb.

 otherwise
 it will hide the global package. I should only install those packages
 which are not in global namespace. Am i correct ?

The dependencies are checked by cabal,

$ cabal install foo --dry-run

should produce something like

In order, the following would be installed (use -v for more details):
bar-0.3.0.0
baz-1.0.5
foo-2.4.1

If any of the packages listed to be installed are already present, you 
*may* have a problem.

If you already have the exact version of one of them, that's certainly a 
problem (cabal wouldn't want to reinstall the same version unless 
something's broken).

If cabal wants to install a newer (or older) version of a package ghc 
itself depends on, that'll almost certainly break some things. If you don't 
change the global package db after the ghc-install, appearance in the 
global db is a simple criterion (though not perfect, installing a newer 
Cabal can be safe, and multiple versions of the same package in the user-db 
can also break things).

In any case, cabal wanting to install a package you already have (and be it 
a different version) is cause for concern, one should check whether it 
looks reasonable.
[The most common reason for cabal wanting to install a newer version of a 
present package is that some package you want to install depends on a newer 
version than you have. That's not a problem per se, but using two packages 
depending on different versions of the same package together usually 
doesn't work, so it might be good to recompile some of your packages 
against the newer version.]

 Any idea how to
 remove this error .
 
 
 ntro@ntro-HP-dx2480-MT-NA121PA:~/Mukesh/Haskell$ ghcghc-7.2.1
 ghci-7.2.1 ghc-pkg-7.2.1
 ntro@ntro-HP-dx2480-MT-NA121PA:~/Mukesh/Haskell$ cabal install keys
 --dry-run -v
 cabal: The program ghc version =6.4 is required but it
 could not be found

Looks bad. The only idea I have is that it could be a PATH issue, your 
global db for 6.12.3 was under /var/lib, and your 7.2.1 lives under 
/usr/local, but it doesn't seem likely.

However, does

$ cabal install --with-compiler=/usr/local/bin/ghc-7.2.1 -v keys --dry-run

work?

  ntro@ntro-HP-dx2480-MT-NA121PA:~/Mukesh/Haskell$ which  ghc-7.2.1
 /usr/local/bin/ghc-7.2.1

Does there exist an unversioned ghc? What does

$ which ghc

print?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error in Installing Data.deriveTH

2011-09-15 Thread Daniel Fischer
On Thursday 15 September 2011, 21:37:29, mukesh tiwari wrote: 
 I tried to resolve this issue on #haskell and i got suggestion that it
 was due to conflict in
 
 global and local namespace [ see here for more detail
 http://hpaste.org/51376 ].

Yes.The containers in the global db is shadowed by the user containers.

 One idea is i should wipe ~/.ghc and install all the libraries
 individually.

That'll work. If there are only few packages broken, unregistering only 
those could be less work.

$ ghc-pkg check

should indicate whether there's a chance that surgical removal of 
individual packages might be worthwhile. If the breakage is recent and only 
few packages are affected, it is, otherwise wiping out the entire user db 
would likely be simpler.

 Could some one please suggest if there is another idea to
 resolve this issue.

There is no fundamentally different way, the only method to fix broken 
packages is to remove them. The only question is whether it's better to get 
completely rid of the entire user db [and if you have the bad luck of 
having breakage within the global db by doing global installs, you'd 
probably need an entire new ghc installation] or only of individual 
packages.

 Currently i have ghc-6.12.3  and  installing 
 ghc-7.0 will resolve the issue ?

In a certain sense, yes. With a new version of ghc, you start with a clean 
slate without broken packages. However, you could pretty much introduce the 
same kind of breakage with that.

Generally, it's a bad idea to reinstall any library that came with the ghc 
installation (there are some exceptions, e.g. installing a newer version of 
Cabal has a fair chance of not causing havoc).
As rules of thumb,
- don't mess with the global db, user installs only
- don't install any library which already has a version in the global db[*]
- be careful when upgrading any library, it could break everything 
depending on that.

Of course, if you know what you're doing, there can be good reasons to 
break any of these rules, but if you don't know why it's right, it's 
probably wrong.
Although it's tedious, checking all cabal install with a --dry-run first 
helps avoiding breakage.

[*] and if you do, the more packages you have installed, the more likely it 
will break some of those.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] efficient chop

2011-09-14 Thread Daniel Fischer
On Wednesday 14 September 2011, 09:17:16, Kazu Yamamoto wrote:
 You can find the results of my friend:
 
 https://gist.github.com/1215660
 
 Please ignore the Japanese text. Please read the code and the results.
 I'm not sure why you had the different result.

Input size. The lazy foldr combinator gets compiled to a bigger, more 
complicated function. When the input is short, the code size makes it 
slower. But when the input is long, the lazy foldr wins because it can 
produce incremental results while the strict foldr combinator and revChop 
need to traverse the entire list before they can produce anything - except 
for the case of 'spaces', where indeed the strict foldr combinator is 
(slightly) faster.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec: non-greedy 'between'

2011-09-11 Thread Daniel Fischer
On Sunday 11 September 2011, 22:38:30, Scott Lawrence wrote:
 Hey all,
 
 Trying to match C-style comments, I have:
 
   between (string /*) (string */) $ many anyChar
 
 Which doesn't work, because it is equivalent (ignoring returned values)
 to
 
   do {string /*; many anyChar; string */}
 
 If the termination criterion was a single character, then I could use
 noneOf or (satisfy . not), but that doesn't help here.
 
 So... what am I missing?

manyTill

A quick example:

Prelude Text.Parsec parse (do {spaces; string /*; com - manyTill 
anyChar (string */); rmd - getInput; return (com, rmd);})  /* a 
comment */ and code /* and another comment */
Right ( a comment , and code /* and another comment */)

 
 Thanks in advance.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapM is supralinear?

2011-09-08 Thread Daniel Fischer
On Friday 09 September 2011, 00:41:11, Roman Cheplyaka wrote:
 * Ertugrul Soeylemez e...@ertes.de [2011-09-07 16:20:03+0200]
 
  In general it's a bad idea to use mapM over IO.
 
 Could you explain why?

Take it with a grain of salt, there's nothing necessarily wrong with using 
mapM over IO on short lists.
The problem is that IO's semantics imply that nothing can be made available 
before the entire list has been consumed and a large thunk is built on the 
way. Thus for longish lists there's a serious risk of stack overflows (or 
even heap exhaustion if you mapM the right [wrong] functions).
The same applies to replicateM, and to other monads with a (=) which 
isn't lazy enough.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] mapM is supralinear?

2011-09-06 Thread Daniel Fischer
On Wednesday 07 September 2011, 01:01:08, Travis Erdman wrote:
 The performance of mapM appears to be supralinear in the length of the
 list it is mapping on.

Hmm. Could reproduce with 6.12.3 and 7.0.4, but not with 7.2.1.

 Does it need to be this way?  

Apparently it doesn't, and it seems to be fixed now.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The maximum/minimum asymmetry

2011-09-05 Thread Daniel Fischer
On Monday 05 September 2011, 08:35:30, Alexander Dunlap wrote:
 On 4 September 2011 21:44, Mario Blažević blama...@acanac.net wrote:
 I was recently surprised to discover that the maximum and maximumBy
  functions always return the *last* maximum, while minimum and
  minimumBy return the *first* minimum in the list. The following GHCi
  session demonstrates this:
  
  $ ghci
  GHCi, version 7.2.1: http://www.haskell.org/ghc/  :? for help
  Loading package ghc-prim ... linking ... done.
  Loading package integer-gmp ... linking ... done.
  Loading package base ... linking ... done.
  Loading package ffi-1.0 ... linking ... done.
  Prelude :module +Data.List Data.Ord
  Prelude Data.List Data.Ord let list = [(1, 'B'), (1, 'A')]
  Prelude Data.List Data.Ord maximumBy (comparing fst) list
  (1,'A')
  Prelude Data.List Data.Ord minimumBy (comparing fst) list
  (1,'B')
  
 I would normally consider this kind of gratuitous asymmetry a bug,
  but seeing that these functions' implementations have been specified
  in the Haskell 98 Library Report, I guess they are now a permanent
  feature of the language. Can anybody explain the reason for this
  behaviour?

 
 The asymmetry is a result of EQ and LT being treated as equivalent in
 both the minBy and maxBy helper functions in the report's definition
 of the two functions, which has opposite effects for minimumBy and
 maximumBy. Since the documentation doesn't specify a behavior for
 equal values, I could guess that it was just an oversight or that it
 was considered unimportant. But maybe someone more knowledgeable will
 correct me.
 
 Alexander Dunlap

The default methods for min and max already have this:

max x y = if x = y then y else x
min x y = if x = y then x else y

I think the reason for this is that if you have

(a, b) = (min x y, max x y),

you'll get both values even if they compare equal (and not everybody thinks 
that if two values compare equal, they shouldn't be distinguishable by any 
other means, so it might matter).

Probably, the behaviour of minimum[By] and maximum[By] is intentional as an 
extension of this.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bitSize

2011-08-29 Thread Daniel Fischer
On Monday 29 August 2011, 12:32:51, Maciej Marcin Piechotka wrote:
 On Fri, 2011-08-26 at 20:30 +0100, Andrew Coppin wrote:
  I suppose I could use a binary logarithm. I'm just concerned that it
  would be rather slow. After all, I'm not interested in the exact
  logarithm (which is fractional), just the number of bits (which is a
  small integer)...
 
 According to random side (http://gruntthepeon.free.fr/ssemath/) not so
 new computers can compute 15.5 milions of serial logarithms per second
 (62 millions in total). I'd say that overhead of Integer might be much
 bigger then cost of logarithm.

Well, converting the Integer to Double can easily take longer than 
calculating the logarithm.

The main problem with this approach, however, is that only smallish 
(cryptographically speaking) Integers can be converted to Double with 
something resembling adequate precision (above 2^1024-2^972, you'll get 
Infinity from the conversion, log is Infinity: boom).


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHCI Feature Request: Last SuccessfulCompilation State Saved

2011-08-28 Thread Daniel Fischer
On Sunday 28 August 2011, 20:43:11, Rene de Visser wrote:
 Daniel Fischer daniel.is.fisc...@googlemail.com schrieb im
 Newsbeitrag news:201108272331.01371.daniel.is.fisc...@googlemail.com...
 
  On Saturday 27 August 2011, 23:10:17, David Virebayre wrote:
  2011/8/27 aditya siram aditya.si...@gmail.com:
   Hi all,
   I would like for the GHCI interpreter to save its environment
   before reloading a file and allowed the user to revert back to
   that state if the compilation was unsuccessful.
  
  That would be awesome. I would like this too.
  
  http://hackage.haskell.org/trac/ghc/ticket/1896
 
 +1 from me too.
 
 How do I go about registering my interest in the ticket?
 I though there was a way of adding myself on the CC: of the ticket?
 How does one do this? Does one need some sort of user?

You need to log in to add yourself to the cc.
If you don't have a trac account and don't want one, at the bottom of the 
page, on the right hand side, there's a pale text telling you how to log in 
with the guest account.

Cheers,
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project Euler: request for comments

2011-08-28 Thread Daniel Fischer
On Monday 29 August 2011, 00:56:52, KC wrote:
 I just noticed that the 20x20 grid has some 00 entries; thus, time
 could be saved by not touching any of the grid entries 3 cells away.
 Same for the 01 entries.
 
 The challenge, of course, is in finding these entries in the first
 place. :)

Multiplication is cheap, looking for zeros (or ones) would take much more 
time than the multiplications one could avoid, so it'd be a net loss (it 
could become a gain if longer sequences were to be considered; depends on 
the proportion of zeros in the grid and the length).

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project Euler: request for comments

2011-08-27 Thread Daniel Fischer
On Saturday 27 August 2011, 02:34:24, Oscar Picasso wrote:
 Hi,
 
 I order to improve my Haskell skills I started (again) to solve the
 project euler problems with this language.
 I am now at problem 11 and would really appreciate any comment about
 my code in order to make it more elegant or efficient.

I don't see any code, where would I have to look?

 
 My solutions can be found here: http://fp.opicasso.com/tag/projecteuler
 
 Oscar Picasso


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project Euler: request for comments

2011-08-27 Thread Daniel Fischer
On Saturday 27 August 2011, 16:03:46, Oscar Picasso wrote:
 Daniel,
 
 There are included as gists on the link provided. After your remark, I
 looked at the generated html code in my blog. The gists are actually
 displayed by running a javascript.
 Maybe your browser settings don't allow to display them.

NoScript :)
I allowed oscarpicasso.com, but didn't look far enough to allow github.com.

 On Sat, Aug 27, 2011 at 4:47 AM, Daniel Fischer
 
 daniel.is.fisc...@googlemail.com wrote:
  On Saturday 27 August 2011, 02:34:24, Oscar Picasso wrote:
  Hi,
  
  I order to improve my Haskell skills I started (again) to solve the
  project euler problems with this language.
  I am now at problem 11 and would really appreciate any comment about
  my code in order to make it more elegant or efficient.

In problem 11, by regarding all 4x4 subgrids separately, you recompute most 
of the horizontal and vertical products up to four times. Also you 
repeatedly use length and (!!). For a problem with such small parameters, 
it doesn't matter much, but consider a 1000x1000 grid with 100x100 
subgrids, it would really hurt then.
You could get much better performance (and no worse code) by using an array 
for the grid.

horizontalProd size grid row col 
= product [grid!(row, col+i) | i - [0 .. size-1]]

verticalProd size grid row col
= product [grid!(row+i, col) | i - [0 .. size-1]]

seProd size grid row col
= product [grid!(row+i, col+i) | i - [0 .. size-1]]

neProd size grid row col
= product [grid!(row-i, col+i) | i - [0 .. size-1]]

maxProd size grid rows cols
= maximum $
 [horizontalProd size grid row col 
 | row - [0 .. rows-1], col - [0 .. cols-size]]
  ++ [verticalProd size grid row col
 | col - [0 .. cols-1], row - [0 .. rows-size]]
  ++ [seProd size grid row col
 | row - [0 .. rows-size], col - [0 .. cols-size]]
  ++ [neProd size grid row col
 | row - [size-1 .. rows-1], col - [0 .. cols-size]]



Another thing,

slice n = takeWhile ((n ==) . length) . map (take n) . tails

if you also import tails from Data.List.

Concerning the newly posted problem 12: Yes, it would be much faster to 
count the divisors using the prime factorisation (plus, there's another 
speedup available if you go that route).

  
  I don't see any code, where would I have to look?
  
  My solutions can be found here:
  http://fp.opicasso.com/tag/projecteuler
  
  Oscar Picasso


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Project Euler: request for comments

2011-08-27 Thread Daniel Fischer
On Saturday 27 August 2011, 17:31:41, Oscar Picasso wrote:
 As a side note, my domain name is not oscarpicasso.com. It was already
 taken by someone else so I decided to use opicasso.com

Oh, yeah, it was that I allowed, misremembered the domain name.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Modules and a main function

2011-08-27 Thread Daniel Fischer
On Saturday 27 August 2011, 22:24:03, michael rice wrote:
 I'm not sure how to do that. Please demonstrate.
 
 Michael

ghc -O -main-is StateGame --make StateGame

more generally,

ghc -O -main-is Foo.bar --make Foo

if the desired main is function bar in module Foo.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GHCI Feature Request: Last Successful Compilation State Saved

2011-08-27 Thread Daniel Fischer
On Saturday 27 August 2011, 23:10:17, David Virebayre wrote:
 2011/8/27 aditya siram aditya.si...@gmail.com:
  Hi all,
  I would like for the GHCI interpreter to save its environment before
  reloading a file and allowed the user to revert back to that state if
  the compilation was unsuccessful.
 
 That would be awesome. I would like this too.

http://hackage.haskell.org/trac/ghc/ticket/1896


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bitSize

2011-08-26 Thread Daniel Fischer
On Friday 26 August 2011, 19:24:37, Andrew Coppin wrote:
 On 26/08/2011 02:40 AM, Daniel Peebles wrote:
  And as Daniel mentioned earlier, it's not at all obvious what we mean
  by bits used when it comes to negative numbers.
 
 I guess part of the problem is that the documentation asserts that
 bitSize will never depend on its argument. (So would will write things
 like bitSize undefined :: ThreadID or similar.)

I don't think that's a problem, it's natural for what bitSize does. And it 
would be bad if bitSize did something different for Integer than for Int, 
Word, ...

 
 I can think of several possible results one might want from a bit size
 query:

Yup, though for some there are better names than bitSize would be.

 
 1. The number of bits of precision which will be kept for values of this
 type. (For Word16, this is 16. For Integer, this is [almost] infinity.)

Not almost infinity, what your RAM or Int allow, whichever cops out 
first, or enough, unless you [try to] do really extreme stuff.

 
 2. The amount of RAM that this value is using up. (But that would surely
 be measured in bytes, not bits. And processor registors make the picture
 more complicated.)
 
 3. The bit count to the most significant bit, ignoring sign.
 
 4. The bit count to the sign bit.
 
 Currently, bitSize implements #1. I'm not especially interested in #2. I
 would usually want #3 or #4.

I'd usually be more interested in #2 than in #4.

 
 Consider the case of 123 (decimal). The 2s complement representation of
 +123 is
 
 ...000011
 
 The 2s complement representation of -123 is
 
 ...111101
 
 For query #3, I would expect both +123 and -123 to yield 7.

One could make a case for the answer 3 for -123, I wouldn't know what to 
expect without it being stated in the docs.

 For query
 #4, I would expect both to yield 8. (Since if you truncate both of those
 strings to 8 bits, then the positive value starts with 0, and the
 negative one start with 1.)

#4 would then generally be #3 + 1 for signed types, I think, so not very 
interesting, but for unsigned types?

 
 Then of course, there's the difference between count of the bits and
 bit index, which one might expect to be zero-based. (So that the Nth
 bit represents 2^N.)

Yes, but that shouldn't be a problem with good names.

So, which of them are useful and important enough to propose for inclusion?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] RFC: decodeFloat

2011-08-26 Thread Daniel Fischer
Occasionally, the behaviour of decodeFloat and its consequences causes 
concern and/or bug reports (e.g. 
http://hackage.haskell.org/trac/ghc/ticket/3898).

The main problem is the treatment of NaNs and infinities (that it doesn't 
distinguish between 0.0 and -0.0 is a minor thing), which are converted as 
if they were ordinary finite values.

Thus, for example, decodeFloat (1/0 :: Double) = (2^52,972) and 
consequently

floor (1/0 :: Double) = 2^1024 (corresponding for round, truncate, ceiling, 
properFraction),
significand (1/0 :: Double) = 0.5,
Prelude uncurry encodeFloat (decodeFloat (1/0 :: Float)) :: Double
3.402823669209385e38

and similar meaningless/nonsensical results for NaNs.

At its type, decodeFloat :: RealFloat a = a - (Integer, Int), I see only 
two reasonable options,

1. leave the behaviour as it is, just warn about the exceptional cases in 
the documentation,

2. let decodeFloat raise an error when its argument is a NaN or infinite.

Both options have disadvantages, 1. makes it easy to get meaningless 
results when there's a non-finite value around, 2. incurs a nontrivial 
performance penalty.

Paying that performance penalty when dealing only with known-to-be-good 
values is undesirable, but so are meaningless results.


A third option would be providing both behaviours by adding a function.
That could take several forms,

a) leave decodeFloat as is and add safeDecodeFloat outside the RealFloat 
class, that would check the value first and then either raise an error on 
NaN/Infinity or return a Maybe (Integer, Int),

b) add a function to the RealFloat class, either leave decodeFloat as is 
and add safeDecodeFloat with the behaviour as in a) or change decodeFloat 
according to 2. and add unsafeDecodeFloat with the current behaviour.

The drawback of a) is that safeDecodeFloat would have to perform two 
checks, while with IEEE Doubles/Floats, the result could be determined by 
one check (which would also be simpler than each of isNaN and isInfinite).
Also, which module should export it?

The drawback of b) is adding a function to RealFloat, as if that wasn't big 
enough already. Since both behaviours allow a default definition in terms 
of the other, only code that by chance uses the new name would break.

What would be the community's preferred way to handle this issue?

Cheers,
Daniel

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bitSize

2011-08-26 Thread Daniel Fischer
On Friday 26 August 2011, 21:30:02, Andrew Coppin wrote:
 You wouldn't want to know how many bits you need to store on disk to 
 reliably recreate the value? Or how many bits of randomness you need to 
 compute a value less than or equal to this one?
 
 I suppose I could use a binary logarithm. I'm just concerned that it 
 would be rather slow. After all, I'm not interested in the exact 
 logarithm (which is fractional), just the number of bits (which is a 
 small integer)...

As of GHC-7.2, there's GHC.Integer.Logarithms in both, integer-gmp and 
integer-simple, providing

integerLog2# :: Integer - Int#

(integer-* lives before base, so there's no Int yet) which exploits the 
representation of Integers and should be fast enough [at least for
integer-gmp, where it's bounded time for normally represented values, the 
representation of Integers in integer-simple forces it to be O(log n)].

Caution: integerLog2# expects its argument to be positive, havoc might 
ensue if it isn't.

GHC.Float exports

integerLogBase :: Integer - Integer - Int

also before 7.2, now it calls the above if the base is 2, so should have 
decent performance. (It requires that the base is  1 and the second 
argument positive, of course.)

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] bitSize

2011-08-25 Thread Daniel Fischer
On Thursday 25 August 2011, 19:57:37, Andrew Coppin wrote:
 Quoting the Haddock documentation for Data.Bits.bitSize:
 
 Return the number of bits in the type of the argument. The actual value
 of the argument is ignored. The function bitSize is undefined for types
 that do not have a fixed bitsize, like Integer.
 
 Does anybody else think it would be *far* more useful if bitSize applied
 to an Integer would tell you how many bits that particular Integer is
 using? Especially given that it can vary?

I'm not sure about that.

 
 Is there a way to actually determine how many bits are in an Integer?
 

Sure. The exact method depends on what result you want and which integer-* 
package you use.

You have to handle 0 and negative n first (how to treat negative n is not 
obvious).

Then, for n  0, f you want 'index of highest set bit' (+1),

(1 +) integerLogBase 2 n

does the trick (integerLogBase is available from GHC.Float, as of 7.2.1, 
it's decently fast).

If you want 'WORD_SIZE_IN_BITS * number of words used', you could use the 
above and round up to the next multiple of WORD_SIZE_IN_BITS, or you could 
make use of the representation of Integers; with integer-gmp,

data Integer
= S# Int#
| J# Int# ByteArray#

so

usedWords (S# _) = 1
usedWords (J# s# _) = I# s#

(nota bene, I don't think it's positively guaranteed that the highest order 
word in a (J# _ _) is nonzero, so usedWords could give a higher answer than 
rounding up from integerLogBase 2 n).

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] different results after compilation

2011-08-24 Thread Daniel Fischer
On Wednesday 24 August 2011, 14:45:19, Комар Максим wrote:
 I have some script:
 $ runhaskell readfile.hs
 fromList [(Merchant {nick = 01010, location = prontera, x = 184, y
 = 94},Shop {buy = ShopBuy {titleB = AB Green Salad=5k, itemsB =
 fromList [(Item {itemId = 12065, price = 5000, refine = , card1 = 0,
 card2 = 0, card3 = 0, card4 = 0},(100,97))]}, sell = ShopSell {titleS =
 , itemsS = fromList []}})]
 $ ghc --make readfile.hs
  Linking readfile ...
 $ ./readfile
 $
 
 why results are different?

Can we see the code?


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using - as both type and value constructor

2011-08-24 Thread Daniel Fischer
On Wednesday 24 August 2011, 20:24:14, Armando Blancas wrote:
 Studying the paper *A Simple Implementation for Priority Search Queues*,
 by Ralf Hinze, I came across the following syntax that I didn't
 understand and I couldn't use in GHCi 7.0.3 for defining a binding data
 type (page 3):
 
 Bindings are represented by the following data type:
 *data k - p = k - p*
 key :: (k - p) - k
 key (k - p) = k
 prio :: (k - p) - p
 prio (k - p) = p
 Note that we use '-' both as a type constructor and value constructor.
 [...] data PSQ k p
 
 The following page has these value constructors:
 
 *0 :: PSQ k p*
 *{.} :: (k - p) - PSQ k p*
 
 
 The paper says that's Haskell '98 code.

I didn't see that claim in the linked slides, and it's not Haskell '98 (nor 
Haskell 2010).
There's a translation of the principles to Haskell from page 17 on or so.

 I'll appreciate info on what
 kind of data declaration those are and any pointers to related
 documentation. Or maybe those are deprecated features.

I don't think the notation from the beginning ever was legal Haskell, I 
think it was chosen to present the ideas separated from syntax.

 I'm stuck in this part.
 
 -armando
 
 www.cs.ox.ac.uk/people/ralf.hinze/talks/ICFP01.pdf


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how long could it wait for an account on hackageDB?

2011-08-23 Thread Daniel Fischer
On Tuesday 23 August 2011, 16:14:43, Qi Qi wrote:
 Hello all,
 
 I wanted to have an account on hackageDB to upload a package. I followed
 http://hackage.haskell.org/packages/accounts.html, and sent an email to
 r...@soi.city.ac.uk for asking an account. It's been a couple days that
 I haven't heard back. Is this normal, or I have to do something else?

Normally, he responds faster. It's not entirely unlikely that he's on 
vacation, though, so perhaps it'll take a bit longer this time of year.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] how to read CPU time vs wall time report from GHC?

2011-08-14 Thread Daniel Fischer
On Sunday 14 August 2011, 21:53:21, Iustin Pop wrote:
 On Sun, Aug 14, 2011 at 08:32:36PM +0200, Wishnu Prasetya wrote:
  On 14-8-2011 20:25, Iustin Pop wrote:
  On Sun, Aug 14, 2011 at 08:11:36PM +0200, Wishnu Prasetya wrote:
  Hi guys,
  
  I'm new in parallel programming with Haskell. I made a simple test
  program using that par combinator etc, and was a bit unhappy that it
  turns out to be  slower than its sequential version. But firstly, I
  dont fully understand how to read the runtime report produced by GHC
  
  with -s option:
 SPARKS: 5 (5 converted, 0 pruned)
 
 INIT  time0.02s  (  0.01s elapsed)
 MUT   time3.46s  (  0.89s elapsed)
 GCtime5.49s  (  1.46s elapsed)
 EXIT  time0.00s  (  0.00s elapsed)
 Total time8.97s  (  2.36s elapsed)
  
  As I understand it from the documentation, the left time-column is
  the CPU time, whereas the right one is elapses wall time. But how
  come that the wall time is less than the CPU time? Isn't wall time =
  user's perspective of time; so that is CPU time + IO + etc?
  
  Yes, but if you have multiple CPUs, then CPU time accumulates
  faster than wall-clock time.
  
  Based on the above example, I guess you have or you run the program
  on 4 cores (2.36 * 4 = 9.44, which means you got a very nice ~95%
  efficiency).
  
  regards,
  iustin
  
  That makes sense... But are you sure thats how i should read this?
 
 As far as I know, this is correct.

It is indeed. CPU time is the sum of CPU time for all threads, which is 
typically larger than elapsed time when several threads run in parallel.

 
  I dont want to jump happy too early.
 
 Well, you algorithm does work in parallel, but if you look at the GC/MUT
 time, ~60% of the total runtime is spent in GC, so you have a space leak
 or an otherwise inefficient algorithm.

Not enough data to make more than guesses concerning the cause, but 60% GC 
definitely indicates a problem with the algorithm (resp. its 
implementation),

 The final speedup is just
 3.46s/2.36s, i.e. 1.46x instead of ~4x, so you still have some work to
 do to make this better.

We don't know the times for a non-threaded run (or an -N1 run), so it could 
be anything from a slowdown to a  4× speedup (but it's likely to be a 
speedup by a factor  4×).

 
 At least, this is how I read those numbers.
 
 regards,
 iustin

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   3   4   5   6   7   8   9   10   >