Re: [Haskell-cafe] Unexpected behaviour with send and send-buffer setting

2013-09-04 Thread Bryan O'Sullivan
On Tue, Sep 3, 2013 at 3:56 PM, Simon Yarde simonya...@me.com wrote:

 I'm new to Haskell and have reached an impasse in understanding the
 behaviour of sockets.


Your question is actually not related to Haskell at all, but is a general
I don't understand socket programming question. You're being misled by
the non-blocking sockets observation - this makes no difference to the
behaviour of your program.

I recommend picking up copies of Unix Network Programming and TCP/IP
Illustrated, and reading them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] sequence causing stack overflow on pretty small lists

2013-08-26 Thread Bryan O'Sullivan
On Mon, Aug 26, 2013 at 1:46 AM, Niklas Hambüchen m...@nh2.me wrote:

 This is because sequence is implemented as

  sequence (m:ms) = do x - m
   xs - sequence ms
   return (x:xs)

 and uses stack space when used on some [IO a].


This problem is not due to sequence, which doesn't need to add any
strictness here. It occurs because the functions in System.Random are
excessively lazy. In particular, randomIO returns an unevaluated thunk.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Markdown extension for Haddock as a GSoC project

2013-04-27 Thread Bryan O'Sullivan
On Sat, Apr 27, 2013 at 2:23 AM, Alistair Bayley alist...@abayley.orgwrote:

 How's about Creole?
 http://wikicreole.org/

 Found it via this:

 http://www.wilfred.me.uk/blog/2012/07/30/why-markdown-is-not-my-favourite-language/

 If you go with Markdown, I vote for one of the Pandoc implementations,
 probably Pandoc (strict):
 http://johnmacfarlane.net/babelmark2/

 (at least then we're not creating yet another standard...)


Probably the best way to deal with this is by sidestepping it: make the
support for alternative syntaxes as modular as possible, and choose two to
start out with in order to get a reasonable shot at constructing a suitable
API.

I think it would be a shame to bikeshed on which specific syntaxes to
support, when a lot of productive energy could more usefully go into
actually getting the work done. Better to say prefer a different markup
language? code to this API, then submit a patch!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Markdown extension for Haddock as a GSoC project

2013-04-27 Thread Bryan O'Sullivan
On Sat, Apr 27, 2013 at 1:47 PM, Ben midfi...@gmail.com wrote:

 asciidoc has been mentioned a few times in comments, i think it's worth
 looking at.


This is the problem I was afraid of: for every markup syntax under the sun,
someone will come along to champion it.

The choice of one or N syntaxes is ultimately up to the discretion of the
student, guided by their mentor. It is in our collective interest to avoid
prolonging a bikeshed discussion on this, as a long inconclusive discussion
risks dissuading any sensible student or mentor from wanting to pursue the
project in the first place.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Stream fusion and span/break/group/init/tails

2013-04-24 Thread Bryan O'Sullivan
On Wed, Apr 24, 2013 at 10:47 AM, Duncan Coutts 
duncan.cou...@googlemail.com wrote:

 I address it briefly in my thesis [1], Section 4.8.2. I think it's a
 fundamental limitation of stream fusion.


See also concat, where the naive fusion-based implementation has quadratic
performance:

concat :: [Text] - Text
concat txts = unstream (Stream.concat (List.map stream txts))

I've never figured out how to implement this with sensible characteristics
within the fusion framework.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] my Fasta is slow ;(

2012-12-28 Thread Bryan O'Sullivan
I've already submitted it, thanks.

The Fortran program commits the same sin as the C++ one, of doing floating
point arithmetic in the inner loop; that's why it's slow.

On Dec 27, 2012, at 18:05, Branimir Maksimovic bm...@hotmail.com wrote:

 Thank you. Your entry is great. Faster than fortran entry!
Dou you want to contribute at the site, or you want me to do it for you?

--
Date: Thu, 27 Dec 2012 15:58:40 -0800
Subject: Re: [Haskell-cafe] my Fasta is slow ;(
From: b...@serpentine.com
To: bm...@hotmail.com
CC: haskell-cafe@haskell.org

On Tue, Dec 18, 2012 at 12:42 PM, Branimir Maksimovic bm...@hotmail.comwrote:


Seems to me that culprit  is in function random as I have tested rest of
code
and didn't found speed related  problems.


The problem with your original program was that it was not pure enough.
Because you stored your PRNG state in an IORef, you forced the program to
allocate and case-inspect boxed Ints in its inner loop.

I refactored it slightly to make genRand and genRandom pure, and combined
with using the LLVM back end, this doubled the program's performance, so
that the Haskell program ran at the same speed as your C++ version.

The next bottleneck was that your program was performing floating point
arithmetic in the inner loop. I changed it to precompute a small lookup
table, followed by only using integer arithmetic in the inner loop (the
same technique used by the fastest C fasta program). This further improved
performance: the new Haskell code is 40% faster than the C++ program, and
only ~20% slower than the C program that currently tops the shootout chart.
The Haskell source is a little over half the size of the C source.

You can follow the work I did here: https://github.com/bos/shootout-fasta
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] my Fasta is slow ;(

2012-12-27 Thread Bryan O'Sullivan
On Tue, Dec 18, 2012 at 12:42 PM, Branimir Maksimovic bm...@hotmail.comwrote:


 Seems to me that culprit  is in function random as I have tested rest of
 code
 and didn't found speed related  problems.


The problem with your original program was that it was not pure enough.
Because you stored your PRNG state in an IORef, you forced the program to
allocate and case-inspect boxed Ints in its inner loop.

I refactored it slightly to make genRand and genRandom pure, and combined
with using the LLVM back end, this doubled the program's performance, so
that the Haskell program ran at the same speed as your C++ version.

The next bottleneck was that your program was performing floating point
arithmetic in the inner loop. I changed it to precompute a small lookup
table, followed by only using integer arithmetic in the inner loop (the
same technique used by the fastest C fasta program). This further improved
performance: the new Haskell code is 40% faster than the C++ program, and
only ~20% slower than the C program that currently tops the shootout chart.
The Haskell source is a little over half the size of the C source.

You can follow the work I did here: https://github.com/bos/shootout-fasta
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] my Fasta is slow ;(

2012-12-19 Thread Bryan O'Sullivan
I took your Haskell program as a base and have refactored it into a version
that is about the same speed as your original C++ program. Will follow up
with details when I have a little more time.

On Tue, Dec 18, 2012 at 12:42 PM, Branimir Maksimovic bm...@hotmail.comwrote:

  This time I have tried fasta benchmark since current entries does not
 display correct output.
 Program is copy of mine
 http://benchmarksgame.alioth.debian.org/u64q/program.php?test=fastalang=gppid=1
 c++ benchmark, but unfortunately executes more than twice time.

 Seems to me that culprit  is in function random as I have tested rest of
 code
 and didn't found speed related  problems.

 bmaxa@maxa:~/shootout/fasta$ time ./fastahs 2500  /dev/null

 real0m5.262s
 user0m5.228s
 sys 0m0.020s

 bmaxa@maxa:~/shootout/fasta$ time ./fastacpp 2500  /dev/null

 real0m2.075s
 user0m2.056s
 sys 0m0.012s

 Since I am planning to contribute program, perhaps someone can
 see a problem to speed it up at least around 3.5 secs which is
 speed of bench that display incorrect result  (in 7.6.1).

 Program follows:

 {-# LANGUAGE BangPatterns #-}
 {-  The Computer Language Benchmarks Game

 http://shootout.alioth.debian.org/

 contributed by Branimir Maksimovic
 -}

 import System.Environment
 import System.IO.Unsafe

 import Data.IORef
 import Data.Array.Unboxed
 import Data.Array.Storable
 import Data.Array.Base
 import Data.Word

 import Foreign.Ptr
 import Foreign.C.Types

 type A = UArray Int Word8
 type B = StorableArray Int Word8
 type C = (UArray Int Word8,UArray Int Double)

 foreign import ccall unsafe stdio.h
  puts  :: Ptr a - IO ()
 foreign import ccall unsafe string.h
  strlen :: Ptr a - IO CInt

 main :: IO ()
 main = do
 n - getArgs = readIO.head

 let !a = (listArray (0,(length alu)-1)
  $ map (fromIntegral. fromEnum) alu:: A)
 make ONE Homo sapiens alu (n*2) $ Main.repeat a (length alu)
 make TWO  IUB ambiguity codes (n*3) $ random iub
 make THREE Homo sapiens frequency (n*5) $ random homosapiens

 make :: String - String - Int - IO Word8 - IO ()
 {-# INLINE make #-}
 make id desc n f = do
 let lst =  ++ id ++   ++ desc
 a - (newListArray (0,length lst)
 $ map (fromIntegral. fromEnum) lst:: IO B)
 unsafeWrite a (length lst) 0
 pr a
 make' n 0
 where
 make' :: Int - Int - IO ()
 make' !n !i = do
 let line = (unsafePerformIO $
 newArray (0,60) 0 :: B)
 if n  0
 then do
 !c - f
 unsafeWrite line i c
 if i+1 = 60
 then do
 pr line
 make' (n-1) 0
 else
 make' (n-1) (i+1)
 else do
 unsafeWrite line i 0
 l - len line
 if l /= 0
 then pr line
 else return ()

 pr :: B - IO ()
 pr line = withStorableArray line (\ptr - puts ptr)
 len :: B - IO CInt
 len line  = withStorableArray line (\ptr - strlen ptr)

 repeat :: A - Int - IO Word8
 repeat xs !n = do
 let v = unsafePerformIO $ newIORef 0
 !i - readIORef v
 if i+1 = n
 then writeIORef v 0
 else writeIORef v (i+1)
 return $ xs `unsafeAt` i

 random :: C - IO Word8
 random (a,b) = do
 !rnd - rand
 let
 find :: Int - IO Word8
 find !i =
 let
 !c = a `unsafeAt` i
 !p = b `unsafeAt` i
 in if p = rnd
 then return c
 else find (i+1)
 find 0

 rand :: IO Double
 {-# INLINE rand #-}
 rand = do
 !seed - readIORef last
 let
 newseed = (seed * ia + ic) `rem` im
 newran  =  fromIntegral newseed * rimd
 rimd  = 1.0 / (fromIntegral im)
 im, ia, ic :: Int
 im  = 139968
 ia  = 3877
 ic  = 29573
 writeIORef last newseed
 return newran
 where
 last = unsafePerformIO $ newIORef 42

 alu:: [Char]
 alu =
 GGCCGGGCGCGGTGGCTCACGCCTGTAATCCCAGCACTTTGG\
 \GAGGCCGAGGCGGGCGGATCACCTGAGGTCAGGAGTTCGAGA\
 \CCAGCCTGGCCAACATGGTGAAAGTCTCTACTAT\
 \ACATTAGCCGGGCGTGGTGGCGCGCGCCTGTAATCCCA\
 \GCTACTCGGGAGGCTGAGGCAGGAGAATCGCTTGAACCCGGG\
 \AGGCGGAGGTTGCAGTGAGCCGAGATCGCGCCACTGCACTCC\
 \AGCCTGGGCGACAGAGCGAGACTCCGTCTCA

 mkCum :: [(Char,Double)] - [(Word8,Double)]
 mkCum lst = map (\(c,p) - ((fromIntegral.fromEnum) c,p)) $
   scanl1 (\(_,p) (c',p') - (c', p+p')) lst

 homosapiens, iub :: C

 iub' = mkCum [('a',0.27),('c',0.12),('g',0.12),('t',0.27),('B',0.02)
 ,('D',0.02),('H',0.02),('K',0.02),('M',0.02),('N',0.02)
 

Re: [Haskell-cafe] Help optimize fannkuch program

2012-12-03 Thread Bryan O'Sullivan
On Sun, Dec 2, 2012 at 3:12 PM, Branimir Maksimovic bm...@hotmail.comwrote:

 Well, playing with Haskell I have literally trasnlated my c++ program

 http://shootout.alioth.debian.org/u64q/program.php?test=fannkuchreduxlang=gppid=3
 and got decent performance but not that good in comparison
 with c++
 On my machine Haskell runs 52 secs while c++ 30 secs.


Did you compile with -O2 -fllvm?

On my machine:

C++ 28 sec
Mine -O2 -fllvm 37 sec
Yours -O2 -fllvm 41 sec
Mine -O2 48 sec
Yours -O2 54 sec

My version of your Haskell code is here: http://hpaste.org/78705
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help optimize fannkuch program

2012-12-03 Thread Bryan O'Sullivan
On Mon, Dec 3, 2012 at 11:18 AM, Branimir Maksimovic bm...@hotmail.comwrote:

 Thanks ! Should I contribute your version on shootout site?


Do whatever you like with it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can a GC delay TCP connection formation?

2012-11-30 Thread Bryan O'Sullivan
On Tue, Nov 27, 2012 at 11:02 AM, Jeff Shaw shawj...@gmail.com wrote:

 Once each minute, a thread of my program updates a global state, stored in
 an IORef, and updated with atomicModifyIORef', based on query results via
 HDBC-obdc.


Incidentally, what kind of database are you talking to? Issues of FFI
correctness aside, HDBC is in general terribly slow compared to some of the
more DB-specific bindings.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hackage Package Discoverability

2012-10-23 Thread Bryan O'Sullivan
On Tue, Oct 23, 2012 at 5:53 AM, Myles C. Maxfield myles.maxfi...@gmail.com
 wrote:

 I am the author/maintainer of the 'punycode' hackage package. After 4
 months, I just found that punycode conversion already exists in the
 Data.Encoding.BootString package inside the 'encoding' package. I'd like to
 deprecate my package in favor of the 'encoding' package.


Please don't plan to do that. The encoding package may have filled a gap at
some point, but now it looks old, unwieldy, inefficient (String), and weird
(implicit parameters?) to me, and it's mostly obsolete (the standard I/O
library has supported Unicode and encodings for a while now). I would not
use the encodings package myself, for instance.

Your punycode package, in contrast, has a simple API and looks easy to use.
I'd suggest that you supprt the Text type as well as String, but otherwise
please keep it around and maintain it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Fast parsing of unboxed values without boxing them in the parser?

2012-10-22 Thread Bryan O'Sullivan
On Tue, Oct 23, 2012 at 3:26 AM, Eugene Kirpichov ekirpic...@gmail.comwrote:

 I'm thinking that a CPS-style parser type could allow returning an
 unboxed value as a result of the compiler inlining and fusing together
 the parsing code and the code that consumes the parsed value.

 Are there any libraries that work like this?


Both cereal (for binary) and attoparsec (text) are written in a CPS style
that can support this in principle. For parsers of even modest complexity,
GHC won't necessarily succeed at unboxing values, though; you have to
inspect the Core to see if what's going on matches what you're hoping for.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Bryan O'Sullivan
On Mon, Sep 24, 2012 at 5:53 AM, George Giorgidze giorgi...@gmail.comwrote:

 Our second approach to OverloadedLists is to avoid the construction of
 lists altogether. By typechecking and desugaring lists like

 [] ; [x,y,z] ;  ['a' .. 'z'] ;

 as

 mempty ; singleton x `mappend` singleton y `mappend` singleton z ;
 genericEnumFromTo 'a' 'z' ;


This is very interesting.

As Michael mentions later, we already have mechanisms in place to work
around the creation of constant strings for the Text and ByteString types,
and they rely on a combination of GHC rewrite rules and knowledge about the
internal representation of constant strings used by GHC. We are fortunate
that GHC uses a very efficient representation to store constant strings, so
doing the translation is efficient.

Constant lists are another story entirely (for good reason); the generated
object files are bloated and poorly laid out, when for simple types
(integers and whatnot), I'd really like to see a packed array in the .data
section.

I would be interested to see if an approach that avoids list construction
can also aim to achieve a more efficient object file layout, with the
implied goal being to make fast translation to the runtime representation
easily achievable.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Build regressions due to GHC 7.6

2012-08-29 Thread Bryan O'Sullivan
Since the release of the GHC 7.6 RC, I've been going through my packages
and fixing up build problems so that people who upgrade to 7.6 will have a
smooth ride.

Sad to say, my experience of 7.6 is that it has felt like a particularly
rough release for backwards incompatibility. I wanted to quantify the pain,
so I did some research, and here's what I found.

I maintain 25 open source Haskell packages. Of these, the majority have
needed updates due to the GHC 7.6 release:

   - base16-bytestring
   - blaze-textual
   - bloomfilter
   - configurator
   - criterion
   - double-conversion
   - filemanip
   - HDBC-mysql
   - mwc-random
   - pcap
   - pool
   - riak-haskell-client
   - snappy
   - text
   - text-format
   - text-icu

That's 16 out of 25 packages I've had to update. I've also either reported
bugs on, or had to fix, several other people's packages along the way
(maybe four?). So let's say I've run into problems with 20 out of the
combined 29 packages of mine and my upstreams.

The reasons for these problems fall into three bins:

   - Prelude no longer exports catch, so a lot of import Prelude hiding
   (catch) had to change.
   - The FFI now requires constructors to be visible, so CInt has to be
   imported as CInt(..).
   - bytestring finally got bumped to 0.10, so many upper bounds had to be
   relaxed (*cf* my suggestion that the upper-bounds-by-default policy is
   destructive).

It has been a lot of work to test 29 packages, and then modify, rebuild,
and release 20 of them. It has consumed most of my limited free time for
almost two weeks. Worse, this has felt like make-work, of no practical
benefit to anyone beyond scrambling to restore the status quo ante.

If over half of my packages needed fixing, I'm alarmed at the thought of
the effects on the rest of Hackage.

I'm torn over this. I understand and agree with the impetus to improve the
platform by tidying things up, and yet just two seemingly innocuous changes
(catch and FFI) have forced me to do a bunch of running to stand still.

I don't have any suggestions about what to do; I know that it's hard to
estimate the downstream effects of what look like small changes. And so I'm
not exactly complaining. Call this an unhappy data point.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-28 Thread Bryan O'Sullivan
On Mon, Aug 27, 2012 at 10:52 AM, Bryan O'Sullivan b...@serpentine.comwrote:

 The reason you're seeing build breakage is that the .cabal files of the
 broken packages were edited in-place without communicating with any of the
 package authors.


Not to flog a dead horse, but:

Just yesterday we had a communication from someone on the Gentoo Linux
packaging team that their checksum validation for the bloomfilter package
was failing. This problem arose because of the hand-editing of the package,
but confusion arose in the bug report due to misattribution of the source
of the error.

https://github.com/haskell/cabal/issues/1017

Hand-editing uploaded tarballs: just don't do it, kids!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Bryan O'Sullivan
On Mon, Aug 27, 2012 at 9:57 AM, Erik Hesselink hessel...@gmail.com wrote:

 I'm seeing this again, on abstract-deque-0.1.6. Ross, can you fix it again?


Hang on a second.

The reason you're seeing build breakage is that the .cabal files of the
broken packages were edited in-place without communicating with any of the
package authors.

I understand that the collective intentions around this were good, but by
fixing things without telling anyone, package maintainers have no way to
know that anything has happened. Now we are seeing the problem begin to
recur as people issue new releases that don't incorporate those changes.

So. Let's have a little conversation about how to handle this sustainably
before wasting more of Ross's time.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Cabal install fails due to recent HUnit

2012-08-27 Thread Bryan O'Sullivan
On Mon, Aug 27, 2012 at 11:39 AM, Erik Hesselink hessel...@gmail.comwrote:


 Yes, you are right. So the question is how long to support systems
 with the old cabal 0.10. This is the one included with the previous
 haskell platform (and thus lots of linux distro's), which is less than
 a year old. But it's also pretty old, since there weren't any cabal
 releases for a while.


That's a very awkward situation. At least in the future, Johan and I have a
proposal to make this class of problem more avoidable by introducing a
regular release schedule. See the thread that starts here for details:
http://www.haskell.org/pipermail/cabal-devel/2012-August/008987.html

For the state of things today, it's not obvious to me what to do.

It's burdensome to ask package authors to remove stuff from their packages
because it can't be handled by a broken version of cabal, especially since
there's no upper bound on how long that broken version will be floating
around. We'd essentially be giving up on this feature semi-permanently,
which would make me sad because it's so useful.

Just as unappealing is the idea of breaking builds for people who, through
no fault of their own, are using the broken cabal. However, at least this
class of people has the incentives aligned to do something about their
problem: either upgrade cabal-install or their distro.

The other question is how useful test suites in a released package
 are. Aren't they much more useful (and used more often) in source
 repositories?


They're certainly useful in source repositories, and we have historically
chosen not to make a distinction between what's in a source repo and what
gets shipped to end users via cabal, which makes sense to me.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Platform Versioning Policy: upper bounds are not our friends

2012-08-17 Thread Bryan O'Sullivan
On Fri, Aug 17, 2012 at 12:34 PM, MigMit miguelim...@yandex.ru wrote:

 What if instead of upper (and lower) bounds we just specify our interface
 requirements?


We already have a simple versioning scheme for which, despite it being easy
to grasp, we have amply demonstrated that we cannot make it work well,
because it has emergent properties that cause it to not scale well across a
large community.

Any vastly more complicated and detailed versioning scheme has a huge
burden to prove that it won't collapse dramatically more quickly. (Frankly,
I think that anything involving specify every detail of your known
dependencies is dead on arrival from a practical standpoint: it's way too
much work.)

For that matter, I think that this burden applies to my own proposal to
omit upper bounds unless they're needed.

Fortunately, we now have several years of historical dependency data that
we can go back and mine, and thereby try to model the effects of particular
suggested changes.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Platform Versioning Policy: upper bounds are not our friends

2012-08-15 Thread Bryan O'Sullivan
Hi, folks -

I'm sure we are all familiar with the phrase cabal dependency hell at
this point, as the number of projects on Hackage that are intended to hack
around the problem slowly grows.

I am currently undergoing a fresh visit to that unhappy realm, as I try to
rebuild some of my packages to see if they work with the GHC 7.6 release
candidate.

A substantial number of the difficulties I am encountering are related to
packages specifying upper bounds on their dependencies. This is a recurrent
problem, and its source lies in the recommendations of the PVP itself
(problematic phrase highlighted in bold):

When publishing a Cabal package, you should ensure that your dependencies
 in the build-depends field are accurate. This means specifying not only
 lower bounds, *but also upper bounds* on every dependency.


I understand that the intention behind requiring tight upper bounds was
good, but in practice this has worked out terribly, leading to depsolver
failures that prevent a package from being installed, when everything goes
smoothly with the upper bounds relaxed. The default response has been for a
flurry of small updates to packages in which the upper bounds are loosened,
thus guaranteeing that the problem will recur in a year or less. This is
neither sensible, fun, nor sustainable.

In practice, when an author bumps a version of a depended-upon package, the
changes are almost always either benign, or will lead to compilation
failure in the depending-upon package. A benign change will obviously have
no visible effect, while a compilation failure is actually *better* than a
depsolver failure, because it's more informative.

This leaves the nasty-but-in-my-experience-rare case of runtime failures
caused by semantic changes. In these instances, a downstream package should
*reactively* add an upper bound once a problem is discovered.

I propose that the sense of the recommendation around upper bounds in the
PVP be reversed: upper bounds should be specified *only when there is a
known problem with a new version* of a depended-upon package.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Platform Versioning Policy: upper bounds are not our friends

2012-08-15 Thread Bryan O'Sullivan
On Wed, Aug 15, 2012 at 1:02 PM, Brandon Allbery allber...@gmail.comwrote:


 So we are certain that the rounds of failures that led to their being
 *added* will never happen again?


Of course I am sure that problems will arise as a result of recommending
that upper bounds be added reactively; didn't I say as much? I expect that
to be a much lesser problem than the current situation.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Platform Versioning Policy: upper bounds are not our friends

2012-08-15 Thread Bryan O'Sullivan
On Wed, Aug 15, 2012 at 1:50 PM, David Thomas davidleotho...@gmail.comwrote:

 Would it make sense to have a known-to-be-stable-though soft upper bound
 added proactively, and a known-to-break-above hard bound added reactively,
 so people can loosen gracefully as appropriate?

I don't think so. It adds complexity, but more importantly it's usual for
the existing upper bounds to refer to versions that don't exist at the time
of writing (and hence can't be known to be stable).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell on Mac OS X Mountain Lion

2012-07-26 Thread Bryan O'Sullivan
On Thu, Jul 26, 2012 at 9:19 AM, mrbuchm...@googlemail.com wrote:

 does the Haskell Platform (2012.2.0.0 I suppose) work on 10.8.


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


Re: [Haskell-cafe] vector, alignment and SIMD through FFI

2012-07-06 Thread Bryan O'Sullivan
On Fri, Jul 6, 2012 at 1:43 PM, Thomas DuBuisson thomas.dubuis...@gmail.com
 wrote:

 The block of memory is sufficiently aligned for any of the basic
 foreign types that fits into a memory block of the allocated size.


That's not the same thing as a guarantee of 16-byte alignment, note, as
none of the standard foreign types have that requirement.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Performance with do notation, mwc-random and unboxed vector

2012-06-15 Thread Bryan O'Sullivan
On Wed, Jun 13, 2012 at 12:56 AM, Roman Leshchinskiy 
r...@cse.unsw.edu.auwrote:


 It doesn't change the semantics of your program but it can make it
 significantly slower (or faster, as in this case). The various state hack
 related tickets on trac might give you an idea of what is happening here.


I filed a bug: http://hackage.haskell.org/trac/ghc/ticket/6166

(I'd CC myself on an existing bug, but trac's search feature gives me tons
of irrelevant hits.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] attoparsec double precision, quickCheck and aeson

2012-06-11 Thread Bryan O'Sullivan
On Mon, Jun 11, 2012 at 10:50 AM, Thomas Schilling
nomin...@googlemail.comwrote:

 Bryan, do you remember what the issue is with C++ in this case?  I
 thought, adding a wrapper with extern C definitions should do the
 trick for simpler libraries (as this one seems to be).  Is the
 interaction with the memory allocator the issue?  Linker flags?


It's specific to ghci, whose object file loader fails to call C++ static
initializers. In the case of the double-conversion library, this means that
static read-only arrays that it assumes to contain valid data are full of
junk.

You can join in the fun over at
http://hackage.haskell.org/trac/ghc/ticket/5289
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] attoparsec double precision, quickCheck and aeson

2012-06-11 Thread Bryan O'Sullivan
On Mon, Jun 11, 2012 at 10:57 AM, Bryan O'Sullivan b...@serpentine.comwrote:



In the case of the double-conversion library, this means that static
 read-only arrays that it assumes to contain valid data are full of junk.
 You can join in the fun over at
 http://hackage.haskell.org/trac/ghc/ticket/5289


Oops, that bug is not actually relevant to this case.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] attoparsec double precision, quickCheck and aeson

2012-06-10 Thread Bryan O'Sullivan
  On Wed, Jun 6, 2012 at 6:20 AM, Doug McIlroy d...@cs.dartmouth.eduwrote:

 Last I looked (admittedly quite a while ago), the state of
 the art was strtod in http://www.netlib.org/fp/dtoa.c.
 (Alas, dtoa.c achieves calculational perfection via a
 murmuration of #ifdefs.)


That was indeed the state of the art for about three decades, until Florian
Loitsch showed up in 2010 with an algorithm that is usually far faster:
http://www.serpentine.com/blog/2011/06/29/here-be-dragons-advances-in-problems-you-didnt-even-know-you-had/

Unfortunately, although I've written Haskell bindings to his library, said
library is written in C++, and our FFI support for C++ libraries is
negligible and buggy. As a result, that code is disabled by default.

It's disheartening to hear that important Haskell code has
 needlessly fallen from perfection--perhaps even deliberately.


Indeed (and yes, it's deliberate). If I had the time to spare, I'd attempt
to fix the situation by porting Loitsch's algorithm to Haskell or C, but
either one would be a lot of work - the library is 5,600 lines of tricky
code.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] attoparsec double precision, quickCheck and aeson

2012-06-05 Thread Bryan O'Sullivan
On Tue, Jun 5, 2012 at 9:12 AM, Warren Harris warrensomeb...@gmail.comwrote:


 which helps in many cases, but for some the parsing seems bi-stable,
 alternating between two imprecise double values and causing the test to
 fail. I was wondering if anyone could suggest a better work-around for this
 problem, or explain why Attoparsec's double parser can't be isomorphic to
 haskell's.


If you need the full precision, use rational instead. The double parser is
there because parsing floating point numbers is often a bottleneck, and
double intentionally trades speed for precision.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Can Haskell outperform C++?

2012-05-24 Thread Bryan O'Sullivan
On Wed, May 23, 2012 at 10:52 PM, Richard O'Keefe o...@cs.otago.ac.nz wrote:

 Past century?  Insults, is it?


Do you fine gentlemen absolutely have to continue this endless, offtopic,
unedifying back-and-forth in public? Please.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Heads up: importing the Cabal issue tracker to github next week

2012-05-16 Thread Bryan O'Sullivan
I am planning on doing this early next week, probably in two phases.

As part of the import process, github will generate a *lot* of notification
emails. I'm afraid there is nothing I can do to stem the tide, as github
does not provide a mechanism to suppress these. If you have a github
account, and you have filed bugs against Cabal in Trac, please brace
yourself.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Too much inlining on text package

2012-04-07 Thread Bryan O'Sullivan
On Sun, Mar 18, 2012 at 12:02 AM, Michael Snoyman mich...@snoyman.comwrote:


 OK, issue created: https://github.com/bos/text/issues/19


I fixed the too-much-inlining
bughttps://github.com/bos/text/commit/2b2cb084c4689c06f1a7851ff8eb1e412eb02c1btonight.
As a bonus, Text literals are now decoded straight from GHC's
packed encoding, without an intermediate step through String.

Generated code now looks like this at -O and above:

$ ghc -O -ddump-simpl -c CS.hs
CS.foo :: Data.Text.Internal.Text
[GblId, ...]
CS.foo = Data.Text.unpackCString# x\NULy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getAddrInfo: does not exist

2012-02-22 Thread Bryan O'Sullivan
On Wed, Feb 22, 2012 at 11:14 AM, Brandon Allbery allber...@gmail.comwrote:


 Note that FreeBSD handles IPv4 vs. IPv6 differently from Windows and
 Linux, and is probably not well tested with the GHC libraries.  It is not
 impossible that there is a lingering bug.


Yeah. I got a bug report from someone about something related to this, but
they didn't offer any useful details, so it's lain fallow awhile. If this
is to be fixed, someone who has BSD experience will have to step up in some
capacity.

Relevant:
http://klickverbot.at/blog/2012/01/getaddrinfo-edge-case-behavior-on-windows-linux-and-osx/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Preventing leaked open file descriptors when catching exceptions

2012-02-21 Thread Bryan O'Sullivan
On Tue, Feb 21, 2012 at 8:16 AM, Ryan Newton rrnew...@gmail.com wrote:

 FYI, lsof confirms that there are indeed many many open connections to the
 same FIFO:


Like all of the lowest-level I/O functions, openFD just gives you back an
integer, and the Fd type has no notion that there's an underlying system
resource associated with it. It's your responsibility to manage it (i.e.
clean up manually when catching an exception).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM atomic blocks in IO functions

2012-01-13 Thread Bryan O'Sullivan
On Fri, Jan 13, 2012 at 10:04 AM, Rob Stewart
robstewar...@googlemail.comwrote:


 The question is a simple one. Must all operations on a TVar happen
 within *the same* atomically block, or am I am I guaranteed thread
 safety if, say, I have a number of atomically blocks in an IO
 function.


If you want successive operations to see a consistent state, they must
occur in the same atomically block.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Package for QuickCheck instances

2012-01-06 Thread Bryan O'Sullivan
On Fri, Jan 6, 2012 at 8:43 AM, Antoine Latter aslat...@gmail.com wrote:


 I was writing some tests that involved a large number of quickcheck
 properties which don't ship with the library itself, so I thought I
 would package them all together and put the orphan instances on
 Hackage.


That's a great idea. Thanks for doing this!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Alternative] some/many narrative

2011-12-15 Thread Bryan O'Sullivan
On Wed, Dec 14, 2011 at 10:29 PM, Chris Wong 
chrisyco+haskell-c...@gmail.com wrote:

-- [Warning]: This is only defined for actions that eventually fail
-- after being performed repeatedly, such as parsing. For pure values
 such
-- as 'Maybe', this will cause an infinite loop.


This is both confusing and incorrect. It's entirely possible for an action
in the Maybe type to fail.

For the Maybe type, failing means an action returns Nothing, and
succeeding means an action returns Just (some value).

If an action of type Maybe a is written to always and unconditionally
return Just some-value-or-other, *that's* when some or many will
infinite-loop if used with it. That doesn't mean there's something wrong
with the definitions of some or many, but rather that they need to be
supplied with an action that will at some point fail.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting off many/some from Alternative

2011-12-14 Thread Bryan O'Sullivan
On Tue, Dec 13, 2011 at 10:23 PM, Gregory Crosswhite
gcrosswh...@gmail.comwrote:


 This way users of the classes will know whether their type has
 well-defined instance for some and many or not.


But that's *precisely* what the Alternative class is already for! If you
are writing an Alternative instance *at all*, then you are asserting that
it *must* be possible and reasonable to replicate the existing behaviour
of some and many.

The fact that those functions are currently methods of the class is
completely irrelevant, and perhaps this is a source of your confusion. They
can be - *and used to be* - implemented as normal functions with
Alternative class constraints, then at some point someone moved them into
the class itself, solely to allow implementors to write faster versions.

I think we should take any further discussion off-list. Your messages from
last night betray a deep misunderstanding that I'm not sure everyone else
needs to sit through :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting off many/some from Alternative

2011-12-12 Thread Bryan O'Sullivan
On Sun, Dec 11, 2011 at 9:18 PM, Gregory Crosswhite
gcrosswh...@gmail.comwrote:


 It is only recently that I have been able to grok what some and many are
 even about (I think), and they seem to only make sense in cases where
 executing the Alternative action results in a portion of some input being
 consumed or not consumed.  some v means consume at least one v and
 return the list of items consumed or fail, and many v means consume
 zero or more v and return the list of items consumed or the empty list of
 none are consume.


There is absolutely no implication of consuming anything in the definitions
of many or some. This is how they happen to behave when used in the context
of some parsing libraries, but that's all. If many or some always go into
an infinite loop for some Alternative instance, then I suspect that the
instance itself is either broken or shouldn't exist.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting off many/some from Alternative

2011-12-12 Thread Bryan O'Sullivan
On Mon, Dec 12, 2011 at 9:23 AM, Carl Howells chowell...@gmail.com wrote:

  There is absolutely no implication of consuming anything in the
 definitions
  of many or some. This is how they happen to behave when used in the
 context
  of some parsing libraries, but that's all. If many or some always go
 into an
  infinite loop for some Alternative instance, then I suspect that the
  instance itself is either broken or shouldn't exist.

 So, then...  The instance for Maybe shouldn't exist?


Don't be silly. The purpose of some and many is to be used with combinators
that are expected to fail sometimes. If you use them with combinators that
always succeed, of course you're going to get an infinite loop. Would you
propose to ban recursive functions because they might not terminate?

Apparently the confusion here lies with the fact that the documentation for
some and many are too terse for their behaviour to be easily understood.
That's a whole different category of problem than ban them!.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splitting off many/some from Alternative

2011-12-12 Thread Bryan O'Sullivan
On Mon, Dec 12, 2011 at 9:42 AM, Carl Howells chowell...@gmail.com wrote:


 Well, as I read it, the whole point of this thread was They don't
 make sense for many instances of Alternative.  They should be moved to
 a different class.  It sounded like you were arguing that any
 instance of Alternative where they don't make sense shouldn't be an
 instance of Alternative, instead.


Correct. And your example of some (Just 1) inflooping was not a
counterargument, but rather an illustration that perhaps some people (and
I'm not trying to imply you here, don't worry) don't understand what some
and many are supposed to do.
___
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 Bryan O'Sullivan
On Thu, Dec 8, 2011 at 8:12 AM, Christoph Breitkopf 
chbreitk...@googlemail.com wrote:


 I'm in the process of implementing a container data type, and wonder what
 class instances are generally considered necessary. E.g. is it ok to start
 out with a Show that's adequate for debugging, or is it a 'must' to include
 instances of everything possible (Eq, Ord if possible, Read, Show, Functor,
 ...).


If you're only beginning or partway through the implementation, my advice
would be to simply not worry about instances at all just yet, until you've
got things in reasonable shape. When the time comes, implement the
instances you think appropriate in order of importance, relevance, and
difficulty.

Of course if you're new to the community, it won't be too obvious what's
important or relevant (difficulty should be obvious enough). Basically, aim
at the standard classes first, based on how often you'd expect to use them
yourself.

And what about the more experimental things? Say, DeepSeq, Typeable, Data?


None of those are experimental. They're all frequently used in production
code. DeepSeq is far more important than the other two, though. For
Typeable and Data, you could copy the approach taken by Data.Map and be
fine.

At some point, if you want your container class to be useful to others,
you'll want to implement Foldable and Traversable.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Drawing charts over a lot of data

2011-11-21 Thread Bryan O'Sullivan
On Mon, Nov 21, 2011 at 3:47 PM, Conrad Parker con...@metadecks.org wrote:


 zoom-cache is useful for managing time-series data. There is a
 zoom-cache-gnuplot in development, and it would probably be useful to
 make a tool that uses Chart. I'm happy to help with that :)


Be aware that Chart is pretty slow on large data sets.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Efficient mutable arrays in STM

2011-10-25 Thread Bryan O'Sullivan
On Tue, Oct 25, 2011 at 1:24 PM, Ketil Malde ke...@malde.org wrote:

 You must be a lot more confident than I if you say this without
 benchmarking first. :-) IME, there are (at least) two possible problems
 here, 1) transactions scale (quadratically, I think) with the number of
 TVars touched, so if any transaction touch a large part of the array,
 it's going to cost you, [...]


That woud remain true no matter what, but the current quadratic behaviour is
I believe easily enough fixed by switching to a better data structure than a
list.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] why is Random in System?

2011-08-17 Thread Bryan O'Sullivan
On Wed, Aug 17, 2011 at 8:56 AM, Ryan Newton rrnew...@gmail.com wrote:


 I'm the maintainer of random.  If people could decide on what the
 alternative name would be we could put it through the library proposal
 process.  It seems that one problem at this moment is the lack of a single,
 clear right answer.  Replacing one debatable not-quite-right choice with
 another may not be satisfying ;-).


The entire premise of that discussion seems quite ridiculous. All that
renaming the modules will achieve is the breakage of several hundred
packages. The roots of the module naming hierarchy - Control, Data, System,
and so on - are so muddled and inconsistently used that the best advice you
could give to people who raise this topic is to pretend those roots are
simply not there.

My proposal for this has been to use AES based crypto-prng.


We'd be better off if you could seek consensus from PRNG maintainers on a
fixed-up Random class before attacking this problem, so that we'd have a
better chance of achieving cross-package compatibility.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] why is Random in System?

2011-08-17 Thread Bryan O'Sullivan
On Wed, Aug 17, 2011 at 11:10 AM, Ryan Newton rrnew...@gmail.com wrote:

 The problem with Mersenne twister is that it doesn't split well.  The main
 reason for crypto prng in this package would not be to advertise to people
 that System.Random can be used for security-related apps *but to make
 splitting reasonably safe*.


The more fundamental problem is that splitting is neither well understood
nor generally safe, and as such it should not be in the basic Random class.
A more sensible API would have a Random class that lacks a split operation,
and a SplittableRandom class that permits it, as you mention later in your
message. Most current PRNGs could then be instances of Random, but not
SplittableRandom.

And I think we need splitting, especially as more Haskell programs become
 parallel.


I do not agree here, I'm afraid.

By the way, my mwc-random package is at least as fast as mersenne-twister,
has smaller state, and is pure Haskell.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] why is Random in System?

2011-08-17 Thread Bryan O'Sullivan
On Wed, Aug 17, 2011 at 12:27 PM, Ryan Newton rrnew...@gmail.com wrote:

 The more fundamental problem is that splitting is neither well understood
 nor generally safe, and as such it should not be in the basic Random class.


 Would you mind elaborating?


Certainly. The purpose of splitting a PRNG is to create two new PRNGs, with
the following properties:

   - Long periods
   - The streams generated by each PRNG must be independent
   - Splitting must be fast, while preserving the above two properties

It's very easy to write a split function that gets at least one of these
considerations wrong.


 But I am under the impression that it is well understood by Burton Smith
 and others who have worked on the topic, and that they assure us that using
 AES, RNG's under any series of splits are as strong as those generated in a
 linear sequence.


The trouble is that very few people have worked on this topic - there's
almost no published literature on it. And Burton and his colleagues readily
admit that the technique they suggest is a matter of folk wisdom in the
crypto community.

A typical technical application of a PRNG is for Monte Carlo processes,
where you want to (a) have a very fast PRNG and (b) understand its
properties. Burton's off-the-cuff suggestion is all very well, but we don't
know important things like what the performance or period of that PRNG would
be. For instance, if we don't know a PRNG's period, we don't know when we're
going to start seeing autocorrelations in its output, or if it supports
splitting, how many splits are safe to perform before we start seeing *cross
*-stream correlation. This in turn means that we don't know whether, when,
or why the consumers of our pseudo-random numbers are going to themselves
start producing garbage results, and that's troubling to me.

Could you expound on this also?  The people I know in the parallelism
 community seem to care a lot about deterministic PRNG in parallel programs.


Yep, but don't conflate determinism with splitting. In the imperative world,
you normally know how many CPUs you have, so you initialize one PRNG per
CPU, and simply go from there; there's no need for splitting. In the
parallel community, people are going out of their way to *avoid* splitting.

The only good treatments of this subject that I know are published by the
SPRNG authors at FSU.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Analyzing slow performance of a Haskell program

2011-08-09 Thread Bryan O'Sullivan
On Tue, Aug 9, 2011 at 9:47 AM, Chris Yuen kizzx2+hask...@gmail.com wrote:


 - I was using GHC 32-bit. Int is 32-bit there, so I needed Int64. It turns
 out 64-bit operations in 32-bit programs are just darn slow. Maybe it's a
 Windows problem.


No, GHC calls out to C for 64-bit integer ops on all 32-bit platforms.


 On Linux 64 bit GHC Int is 64 bit so everything just works. Changing Int64
 to Int liberates me from many `fromIntegral` which saved 20%


Actually, fromIntegral is usually a no-op, so chances are you're seeing the
effect of something else.


 - Changing `divMod` to `quotRem` saved another 20%


It's cheaper again to use quotInt# and remInt# as I did in my code.


 1. Why are bangs needed on the length arrays?


GHC has to deconstruct the Vector in order to get at the real underlying
array, so that unsafeIndex can perform the actual index into the real
underlying array.

Without bang patterns, the code performs at least one deconstruction on
every iteration through the loop. Each deconstruction has a cost. With the
bang patterns, they're all hoisted out and performed just once.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Analyzing slow performance of a Haskell program

2011-08-08 Thread Bryan O'Sullivan
On Mon, Aug 8, 2011 at 9:24 AM, Chris Yuen kizzx2+hask...@gmail.com wrote:


 For reference I have asked the same question on StackOverflow. One person
 suggested that the reason might be that Int64 on Windows is broken (
 http://stackoverflow.com/questions/6970904/analyzing-slow-performance-of-a-haskell-program/6976448#6976448
 ).


No, they're barking up the wrong tree.

I've put an idiomatic Haskell translation of your C++ algorithm at
https://gist.github.com/1133048#file_wordy.hs

(I've also included a copy of your original C++, with a bug fixed, in the
same gist.)

As you can see, the two are almost identical. Not surprisingly, each one
spends the bulk of its time computing word lengths.

GHC simply doesn't do a great job of compiling fairly tight code like this.
gcc generates about 100 lines of assembly that's mostly easy to follow
(except for some bit-twiddling tricks to avoid div instructions). Although
the Core it generates looks fine, GHC spends quite a bit of time in its
generated assembly on what looks to me like STG housekeeping (it spends only
0.3% of its time in the garbage collector, because it doesn't allocate
memory). The overall result is that the Haskell code runs about 5x more
slowly than the C++ code.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] trouble using the aeson package

2011-08-06 Thread Bryan O'Sullivan
On Sat, Aug 6, 2011 at 8:55 PM, anonymous qubi...@gmail.com wrote:


 However when I try to use it I receive this error message:


Funny, I just spent some time documenting this earlier today. There are two
bugs in GHCi that cause the problem you're seeing. They're documented here,
with a workaround: https://github.com/mailrank/blaze-textual#readme
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: cabal-dev 0.8

2011-07-18 Thread Bryan O'Sullivan
On Mon, Jul 18, 2011 at 1:10 PM, Rogan Creswick cresw...@galois.com wrote:

 We're happy to announce the release of cabal-dev 0.8! This version is
 available on hackage now, and contains many bug fixes and improvements,
 as outlined in the full release notes below.


Wonderful! This is absolutely one of those indispensable tools for build
automation and sanity preservation. I use cabal-dev to manage the builds for
all of my Haskell projects, under many different configurations:
https://jenkins.serpentine.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] External system connections

2011-07-11 Thread Bryan O'Sullivan
On Mon, Jul 11, 2011 at 10:49 AM, Michael Snoyman mich...@snoyman.comwrote:

 I did email Bryan about this a bit ago, but he didn't get back [...]


Thanks for jogging my memory. I've released an updated version of
resource-pool that drops the dependency on that package.

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


[Haskell-cafe] Jenkins/Hudson support for GHC warnings?

2011-07-07 Thread Bryan O'Sullivan
Hi, folks -

I know there are quite a few Haskell projects using the Jenkins (formerly
Hudson) continuous build system, and I wonder if anyone has figured out how
to get it reliably collecting errors and warnings from GHC. The standard
warnings pluginhttps://wiki.jenkins-ci.org/display/JENKINS/Warnings+Plugindoes
a bad job - it tends to identify random (sometimes even empty) bits of
build output as warnings. If you've configured it to behave better with GHC
/ hpc / QuickCheck / cabal-install, you'd be doing us a great service by
sharing your tricks!

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


Re: [Haskell-cafe] Searching of several substrings (with Data.Text ?)

2011-07-05 Thread Bryan O'Sullivan
On Tue, Jul 5, 2011 at 11:01 AM, Tillmann Vogt tillmann.v...@rwth-aachen.de
 wrote:

 I looked at Data.Text http://hackage.haskell.org/**
 packages/archive/text/0.5/doc/**html/Data-Text.htmlhttp://hackage.haskell.org/packages/archive/text/0.5/doc/html/Data-Text.html
 and http://hackage.haskell.org/**packages/archive/stringsearch/**
 0.3.3/doc/html/Data-**ByteString-Search.htmlhttp://hackage.haskell.org/packages/archive/stringsearch/0.3.3/doc/html/Data-ByteString-Search.html

 but they don't have a function that can search several substrings in one
 run.


Here's what you want:
http://hackage.haskell.org/packages/archive/text-icu/0.6.3.4/doc/html/Data-Text-ICU-Regex.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [ANN] mysql-simple - your go-to package for talking to MySQL

2011-06-21 Thread Bryan O'Sullivan
On Tue, Jun 21, 2011 at 4:45 AM, David Virebayre dav.vire+hask...@gmail.com
 wrote:


 I had trouble accessing the documentation : the last versions on
 hackage have a build failure, so the doc isn't available.


I don't understand why that build failure occurs. You can always build
documentation for a package locally using cabal haddock.


 The very first example didn't work for me :


Oops, thanks for mentioning that. I've fixed the documentation and made the
information about type inference a little clearer.

Indeed, the documentation shows that convertError takes 3 parameters,

and I gave, as per the example, only 2.
 But I'm not sure what to write for the 3rd parameter, the
 documentation doesn't help me here.


Thanks for spotting the omission, I've clarified that. The Int parameter
indicates the number of columns expected for conversion.


 I'm not sure if that means Database.MySQL supports calling stored
 procedures that return a result set or not. I suspect not.


The mysql-simple package currently doesn't support stored procedures or
multi-statement queries. Each of these can return multiple result sets. It
would be necessary to add new functions to the API to support them, as of
course each result set could have a different shape.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [ANN] mysql-simple - your go-to package for talking to MySQL

2011-06-21 Thread Bryan O'Sullivan
On Tue, Jun 21, 2011 at 7:47 AM, David Virebayre dav.vire+hask...@gmail.com
 wrote:

 The problem isn't with the stored procedure, it works if I call it
 from the mysql client.


Right - as I mentioned in my previous note, the problem is that stored
procedures and multi-statement queries can both return multiple result sets.
We can't easily use type inference to express the difference between in
this use of query, I want a single result (the common case) and in this
other use of query, I expect three results, each with different shapes (far
less common), so we need something like a multiQuery function (and perhaps a
MultiResult class) instead.

Another unrelated thing : the documentation states that the Query type
 is designed to make it difficult to create queries by concatenating
 strings.


You can do it, but you have to use the Monoid class's functions, e.g.:
select  `mappend` 2 + 2

For cases like your show columns from example, though, I prefer Chris's
suggestion of creating a custom newtype with its own special Param instance.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Attoparsec concatenating combinator

2011-06-07 Thread Bryan O'Sullivan
On Tue, Jun 7, 2011 at 1:40 AM, Simon Meier iridc...@gmail.com wrote:

 Why would you need 'unsafePerformIO'. You can scrutinise the 'PS'
 constructors of the slice without dropping down to IO.


True. Oops :-)


 Using a Builder for concatentation makes sense, if you want to exploit
 that copying a slice of the input array is cheaper right after it has
 been inspected (its fully cached) than later (as it is done when
 collecting slices in a list).


When I've measured this in the past, I've found that it's often faster to
accumulate a list and then run concat at the end than to use blaze-builder
directly. That was certainly the case wit GHC 6.12; I haven't remeasured
with 7.0. That's why you'll see that some places in the aeson JSON library
use blaze-builder, while others manipulate bytestrings directly.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Attoparsec concatenating combinator

2011-06-06 Thread Bryan O'Sullivan
On Sun, Jun 5, 2011 at 11:00 AM, Yitzchak Gale g...@sefer.org wrote:

 If behind the scenes the concat is copying directly from slices of the
 original
 input, then no, in principle we're not saving much then.
 I thought there were *two* copies going on.


If you're using the specialised functions like attoparsec's takeWhile, then
all they do is return a view into the underlying array. No copying occurs
until the concat itself. Now that I think of it: in principle, you could
write a specialised concat that would check the pointer/offset/length
combinations of its arguments and, if they all abutted perfectly, would just
return a new view into that same array, sans copying. (You'd have to hide it
behind unsafePerformIO, of course.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Attoparsec concatenating combinator

2011-06-03 Thread Bryan O'Sullivan
On Fri, Jun 3, 2011 at 2:52 AM, Yitzchak Gale g...@sefer.org wrote:

 I was thinking of even lower level: allocating a moderate chunk of
 memory and writing the results directly into it consecutively as a
 special case.


Surely that would save only one copy compared to creating a list of results
and then concatenating them, no? I'd be a little surprised if it proved
worthwhile.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Attoparsec concatenating combinator

2011-06-02 Thread Bryan O'Sullivan
On Thu, Jun 2, 2011 at 7:02 AM, Yitzchak Gale g...@sefer.org wrote:

 It seems the best I can do is to collect them all in a list and then
 apply concat. But that still copies the text several times.


Right. I'd like a no-copy combinator for the same reasons, but I think it's
impossible to do without some low-level support.


 If not, does the internal representation easily admit such a combinator?


Not very easily. Internally, attoparsec maintains just three pieces of data
for its state:

   - The current input
   - Any input we received via continuations, in case we need to backtrack
   - A flag that denotes whether we were fed EOF by a continuation

There are no line numbers, no bytes consumed counters, nothing else. If
there was a bytes consumed counter, it would be possible to write a
try-like combinator that would hold onto the current input, run a parser,
tack on any input received via continuations to the original input, and then
use the counter to slice off a portion of that bytestring without copying. I
can't think of another way to do it. Adding that counter would be a moderate
amount of work, and would presumably have a negative effect on performance.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Policy for taking over a package on Hackage

2011-05-25 Thread Bryan O'Sullivan
On Wed, May 25, 2011 at 5:01 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 With my wl-pprint-text package, Jason Dagit suggested to me on
 #haskell that it would make sense to make such a pretty-printer be
 class-based so that the same API could be used for String, ByteString,
 Text, etc.


I don't think that's actually a good idea. The internals of your package
will be a soggy mess, and the public APIs will be hard to follow. I'm also
unclear on why you'd want to use something like wl-pprint for bytestrings at
all.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Policy for taking over a package on Hackage

2011-05-25 Thread Bryan O'Sullivan
On Wed, May 25, 2011 at 5:59 AM, Ivan Lazar Miljenovic 
ivan.miljeno...@gmail.com wrote:

 Well, using the Char8 version.


Just because you *could* do that, it doesn't mean that you *should*. It's a
bad idea to use bytestrings for manipulating text, yet the only plausible
reason to have wl-pprint handle bytestrings is so that they can be used as
text.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hash table constructors return table in IO Monad. Why?

2011-05-12 Thread Bryan O'Sullivan
On Thu, May 12, 2011 at 9:22 AM, Stephen Tetley stephen.tet...@gmail.comwrote:

 The hashtable needs to be been created in IO, after that, think of the
 'hashtable' as a analogous to a file handle. You have to pass it
 around to do anything with it - but the only things you can do with it
 are in IO.


The appropriate pure package to be using instead is unordered-containers.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Hash table constructors return table in IO Monad. Why?

2011-05-12 Thread Bryan O'Sullivan
On Thu, May 12, 2011 at 12:59 PM, michael rice nowg...@yahoo.com wrote:


 HashTable doesn't do it. Neither does Map. Was I dreaming?


multiInsert k v m = insertWith' (++) k [v] m
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using cmake with haskell

2011-05-11 Thread Bryan O'Sullivan
On Wed, May 11, 2011 at 12:54 PM, Robert Clausecker fuz...@gmail.comwrote:

Is it possible to use cmake for Haskell projects?


Yes, but you shouldn't. Just use the cabal build system instead. It solves
the same kinds of problems, but requires far less effort than dealing with
CMake.


I heard about CMake and I think it is a pretty cool product.


It is not. It's a fairly terrible piece of software. It has a grotesque
macro language, lots of strange undocumented behaviours, and is generally a
nightmare to work with. The only thing it's adequate for is managing the
build and packaging of very complex cross-platform software packages. You
certainly shouldn't use it for anything else. In fairness, the CMake
developers are very nice and responsive, which is just as well given the
number of times you'll have to ask them why isn't this doing something
sane? if you use it for a real project.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Please add instance Semigroup Text

2011-05-03 Thread Bryan O'Sullivan
On Tue, May 3, 2011 at 8:00 AM, Yitzchak Gale g...@sefer.org wrote:


 Could you please add a Semigroup instance for Text?


I'd strongly recommend writing an instance for the text package's Builder
type instead. Vastly more efficient for non-trivial jobs.


 Once you're doing that, I suppose you'd also want to
 add it for lazy Text and both kinds of ByteStrings.


Likewise, there's allegedly work afoot to write a builder for bytestrings.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Please add instance Semigroup Text

2011-05-03 Thread Bryan O'Sullivan
On Tue, May 3, 2011 at 1:14 PM, Yitzchak Gale g...@sefer.org wrote:

 You are quite right. These should really be defined in their
 respective packages. I don't think it's too onerous for them
 to add a dependency on semigroups, even before you
 reverse the few lightweight dependencies that semigroups has.


Unfortunately, the semigroups package will have to go into the Platform
before either text or bytestring can make use of it. I think that would be
great to have, but the getting from here to there is not necessarily fun.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [ANN] mysql-simple - your go-to package for talking to MySQL

2011-05-01 Thread Bryan O'Sullivan
Hi, folks -

Over the past few days, I've released two MySQL-related packages on Hackage
that I think should be pretty useful.

The first is mysql-simple: http://hackage.haskell.org/package/mysql-simple

This is a mid-level binding to the MySQL client API. I aimed it squarely at
being both fast and easy to use, and I'm very pleased with the results so
far.

   - Performance: compared to HDBC-mysql, mysql-simple yields a 60%
   performance improvement on my real-world application.
   - Ease of use: compared again to HDBC, my real-world application's
   DB-specific code shrunk by 50% while achieving the above performance
   increase.
   - Type safety: it's intentionally hard to construct SQL queries by string
   concatenation, but of course I provide some nice safe APIs for formatting
   queries and converting results. That safety does not come at the expense of
   performance or expressive bloat, as the above results indicate.

Because I know that some people favour interacting with their databases via
a model such as iteratees, the mysql-simple library is built on top of a
very lightweight library.

That lower-level library is named mysql:
http://hackage.haskell.org/package/mysql

This is a low-level binding to the MySQL client API. It is aimed at high
performance and simplicity, but more specifically for consumption by authors
of higher-level database libraries. It is bare enough of features that it
doesn't even perform conversion between Haskell and SQL types, but at the
same time it uses bytestrings sensibly, cheaply avoids some nasty signal
interruption problems with the MySQL client library, and abstracts some of
the tiresome details of memory management. It gives a higher-level library
complete control over result conversion, how to fetch results, and all that,
so you can focus purely on building iteratees and not the lower-level gunk.

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


Re: [Haskell-cafe] How to update the RNG per call (State monad) when generating QuickCheck arbitraries?

2011-04-26 Thread Bryan O'Sullivan
On Tue, Apr 26, 2011 at 3:04 AM, Daniel Kahlenberg 
d.kahlenb...@googlemail.com wrote:

 Thought getRandom function would be the best place to inject my unGen
 function
 call, but cannot get it to type-check:


You haven't described what it is you're actually trying to do, and I'm
afraid your code doesn't help to understand that.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to update the RNG per call (State monad) when generating QuickCheck arbitraries?

2011-04-26 Thread Bryan O'Sullivan
On Tue, Apr 26, 2011 at 9:16 AM, Daniel Kahlenberg
d.kahlenb...@gmail.comwrote:


 hold on I'd like to have the genArray call generating distinctive
 results in one IO execution


The problem you're seeing is due to the fact that you're not taking the
final RNG state from the first execution of your code and passing it as the
initial state to the second. Since you're initialising each one with the
same RNG state, you're getting the same results in each case.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Hugs dead?

2011-04-22 Thread Bryan O'Sullivan
On Fri, Apr 22, 2011 at 5:16 AM, Robert Clausecker fuz...@gmail.com wrote:


 Now my question is: Is Hugs dead? What's the status of development of
 hugs?


It's been unmaintained for years now.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] NOT Iteratee, ghc 6.12/7.0 strange behaviour -epollControl: permission denied (Operation not permitted)

2011-03-31 Thread Bryan O'Sullivan
On Thu, Mar 31, 2011 at 11:19 AM, Michael A Baikov pa...@bk.ru wrote:

 import System.Posix.IO
 import GHC.Conc

 main = do
fd - openFd /etc/passwd ReadOnly Nothing defaultFileFlags
threadWaitRead fd-- the big bang happens right here.
closeFd fd


There were a couple of bugs in event manager that we fixed some time during
the 7.0.2 or 7.0.3 release cycle. So if you're not running 7.0.3, please do.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANN: unordered-containers - a new, faster hashing-based containers library

2011-02-22 Thread Bryan O'Sullivan
On Sat, Feb 19, 2011 at 11:58 AM, Louis Wasserman wasserman.lo...@gmail.com
 wrote:


 size takes O(n).  That's just depressing.  Really.


That's rather thoughtless wording for some code that's (a) free (b) faster
than anything else currently available (c) in its very first release and (d)
available in source form for you to improve as you see fit. Just depressing.
Really.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Faster timeout but is it correct?

2011-02-17 Thread Bryan O'Sullivan
On Thu, Feb 17, 2011 at 11:53 AM, Bas van Dijk v.dijk@gmail.com wrote:

 Then we can use the TimeoutKey as our Unique (Note that a TimeoutKey
 is actually a newtype for a Unique):


That should be fine. It's not a public API, so changing it like that
shouldn't be an issue.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [web-devel] http-enumerator: redirects, streaming and keep-alive

2011-02-07 Thread Bryan O'Sullivan
On Wed, Feb 2, 2011 at 1:01 PM, Felipe Almeida Lessa felipe.le...@gmail.com
 wrote:


 And what about connection limits?  We shouldn't create a thousand
 connections to the same host =).


For what it's worth, I wrote a connection pool manager for the riak package
that has to solve some of the same problems.

https://github.com/mailrank/riak-haskell-client/blob/master/src/Network/Riak/Connection/Pool.hs
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Using IsString with attoparsec

2011-01-26 Thread Bryan O'Sullivan
On Tue, Jan 25, 2011 at 5:16 AM, Yitzchak Gale g...@sefer.org wrote:

 I suggest adding the following type-specialized variants to
 Data.Attoparsec.Char8:

 (*.) :: Applicative f = f a - f ByteString - f a
 (*.) = (*)

 (.*) :: Applicative f = f ByteString - f a - f a
 (.*) = (*)


Sounds reasonable. Send a patch?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] parsec2 vs. parsec3... again

2011-01-14 Thread Bryan O'Sullivan
On Fri, Jan 14, 2011 at 5:54 PM, Evan Laforge qdun...@gmail.com wrote:



Then I found out that
 compiling with profiling enabled makes attoparsec slow and parsec
 fast.


Yes, the SCC annotations added by GHC have a fairly high cost.

I think my short term solution is going to be remove -auto-all from
 attoparsec's cabal---I'm not profiling attoparsec and so I don't want
 my entire profile output to be internal attoparsec functions.  But
 presumably the flag was added there for a reason, so maybe there are
 people who really want that.


Yes - me :-)

I typically turn on profiling for most of my libraries while I think of them
as under development, a period of indefinite length that comes to an end
when I deem the performance good enough. None of my libraries has actually
hit that point yet :-)

This isn't completely without basis. For instance, I made some big speed
improvements to attoparsec's very performance-sensitive takeWhile function
just the other day, thanks to -auto-all.

I might, though, see if there's a way I could enable that flag only for
myself (in a way that I wouldn't routinely forget).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The Bay Area Haskell Hackathon is coming up: Feb 11-13, 2011

2010-12-26 Thread Bryan O'Sullivan
On Fri, Dec 24, 2010 at 5:32 PM, Alan Shaw noden...@gmail.com wrote:

 I'm a beginner in Haskell (you can see where I'm at from my blog post Haskell
 Liftoff http://nodename.com/blog/2010/12/22/haskell-liftoff/)
 and I want to learn more, but I'm not sure what a hackathon is.


Come along, write code, meet people, exchange ideas, write more code, learn
stuff, have fun, make the rest up yourself :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] The Bay Area Haskell Hackathon is coming up: Feb 11-13, 2011

2010-12-23 Thread Bryan O'Sullivan
Mark Lentczner and I are organizing, and it will be held at Hacker Dojo in
Mountain 
Viewhttp://maps.google.com/maps/place?cid=2122486601784397611q=hacker+dojogl=us
.

If you plan to attend, please fill in our sign-up
formhttps://spreadsheets.google.com/viewform?formkey=dEc5cW1fa3hjQ3JheVF5dHAwdTk0eGc6MQso
we know we'll have room.

Also, please consider joining the Hackathon's Google
grouphttp://groups.google.com/group/bayhac
.

We look forward to seeing you!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splittable random numbers

2010-11-12 Thread Bryan O'Sullivan
On Fri, Nov 12, 2010 at 12:34 PM, Luke Palmer lrpal...@gmail.com wrote:


 Yeah I think a package of randomness tests could be really useful.  Cool
 :-)


There are already well-established suites of very thorough PRNG tests, such
as Diehard and Big Crush. Please don't invent another.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Splittable random numbers

2010-11-12 Thread Bryan O'Sullivan
On Fri, Nov 12, 2010 at 1:28 PM, Richard Senington sc06...@leeds.ac.ukwrote:

 Thankyou for the advice, but since I am just learning about some of this
 stuff, how about I have ago at implementing some of their tests?


Sure. See http://www.iro.umontreal.ca/~simardr/testu01/tu01.html for the
current state of the art.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Splittable random numbers

2010-11-04 Thread Bryan O'Sullivan
On Thu, Nov 4, 2010 at 11:39 AM, Thomas DuBuisson
thomas.dubuis...@gmail.com wrote:
 Before we bother to do that I think it would be worth deciding what
 level of performance we are trying to achieve.  On my laptop (Core2
 2.5Ghz) I generate 4MB of random values in less than 900ms (HashDRBG).
  What is StdGen getting, which I know people consider slow?

I measured StdGen last year as generating around a million values per
second. My mwc-random library is about 100 times faster when running
in the ST monad.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] New repo location for the network package

2010-10-28 Thread Bryan O'Sullivan
On Thu, Oct 28, 2010 at 8:06 AM, Magnus Therning mag...@therning.orgwrote:

 Fair enough.  Do you have enough buy-in to make sure that the github
 organisation becomes the best location for *all* HP packages?

 That is, can I stop going to Hackage to find the home for HP packages?


That's never been our intention. github is for in-progress source trees;
Hackage is for releases of code.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] [ANNOUNCE] text 0.10.0.0 - fast Unicode text handling

2010-10-21 Thread Bryan O'Sullivan
[Blog copy of the announcement
herehttp://www.serpentine.com/blog/2010/10/22/text-0-10-0-0-is-here/
.]

I just pushed it to bitbucket http://bitbucket.org/bos/text and
githubhttp://github.com/bos/text,
and you can install it from the text site on
Hackagehttp://hackage.haskell.org/package/text in
the usual way:

cabal update
cabal install text

What's in this release?

   -

   New functions for reading integers and floating point
numbershttp://hackage.haskell.org/packages/archive/text/0.10.0.0/doc/html/Data-Text-Read.html,
   an oft-requested feature. They're fast, too: they range from parity with
   their bytestring counterparts, to up to 4 times faster. You can expect to
   parse 3 to 4 million Int values per second out of a text file, or up 2
   million Double values per second. They're also easy to use, give error
   messages, and come in strict and lazy variants.
   -

   UTF-8 decoding and encoding are now very
fasthttp://www.serpentine.com/blog/2010/10/15/unicode-text-performance-improvements/.
   They're up to 9x faster than they were, and close to the performance of pure
   C UTF-8 decoding and encoding.
   -

   The Eq and Ord instances are also now very fast, up to 5x faster than
   
beforehttp://www.serpentine.com/blog/2010/10/19/a-brief-tale-of-faster-equality/.
   They're now faster than the bytestring instances.
   -

   Several other common functions received drive-by performance improvements
   too.
   -

   Better protection against rare crashes on really huge volumes of data.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] profiling cabal libraries

2010-10-19 Thread Bryan O'Sullivan
On Tue, Oct 19, 2010 at 8:42 AM, Tom Hawkins tomahawk...@gmail.com wrote:


 I cabal install -p a local package I am testing, and I compile a
 test of the library using -prof -auto-all.  But the profiling report
 only lists a CAF entry for the library, but does not detail any of the
 library's top level functions.


That's expected and normal. You either have to manually add SCC annotations
to code, or if you want the usual automated ones, add the following to your
.cabal file:

ghc-prof-options: -auto-all
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Text: find

2010-10-17 Thread Bryan O'Sullivan
On Sun, Oct 17, 2010 at 1:51 PM, Antoine Latter aslat...@gmail.com wrote:


 What would the definition of a function of the form:

  find :: (Text - Bool) - Text - Maybe Text

 look like?


Can you be more specific? I assume you mean that the only sensible return
values are Nothing or the entire Text for which the predicate first returns
True? (In other words, that this function doesn't actually seem to have a
useful return type.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Notes from Haskell takes over the world BoF at ICFP

2010-10-06 Thread Bryan O'Sullivan
On Wed, Oct 6, 2010 at 12:10 PM, Don Stewart d...@galois.com wrote:

 Here  are the notes transcribed from the Future of Haskell BoF held
 after the Haskell Symposium last week.


Thanks for sending out the notes, Don! It was a very helpful and
constructive session for me, to let me see some interesting opportunities
for helping out the community over the coming year. I very much appreciate
all that people had to say, ugly bits and all :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Problem with monad transformer stack

2010-10-03 Thread Bryan O'Sullivan
On Sun, Oct 3, 2010 at 9:40 PM, Michael Vanier mvanie...@gmail.com wrote:


 {- This doesn't work: -}
 newtype MyMonad a =
  MyMonad ((StateT (MyData a) (Either SomeError) a))
  deriving (Monad,
MonadState (MyData a),
MonadError SomeError,
Typeable)


This simply isn't allowed by the generalised newtype derivation machinery,
because the type variable a appears in one of the classes you're deriving.

In fact, I'm not sure how you're hoping for your type to actually work as a
monad. If you try using (=) on your type synonym that currently appears to
typecheck, you'll find that the only value that can inhabit the state
parameter is bottom. Try writing out and using a definition of (=) by hand
to understand your confusion.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Big Arrays

2010-10-03 Thread Bryan O'Sullivan
On Sun, Oct 3, 2010 at 11:54 AM, Henry Laxen nadine.and.he...@pobox.comwrote:


 I am trying to create a (relatively) big array,
 but it seems I cannot make anything larger
 than 2^30 or so.  Here is the code:


Use a 64-bit machine, where Int is 64 bits wide. Trying to create a larger
array on a 32-bit machine doesn't make any sense.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: text 0.9.0.0 and text-icu 0.4.0.0

2010-09-20 Thread Bryan O'Sullivan
On Sun, Sep 19, 2010 at 9:37 PM, John Millikin jmilli...@gmail.com wrote:


 What's new in text-0.9 ? All I see in darcs is a newtype'd param in
 the Foreign module.


That is all that's new, but the PVP suggests that this requires a version
bump, since it changes an existing interface.

The purpose of the newtype is to make it less likely that one could confuse
indices into the Word16 array with a count of Unicode code points.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: text 0.9.0.0 and text-icu 0.4.0.0

2010-09-19 Thread Bryan O'Sullivan
I've issued new releases of the text and text-icu packages, the fast,
comprehensive Unicode text manipulation libraries.

http://hackage.haskell.org/package/text
http://hackage.haskell.org/package/text-icu

Features of text:

   - Compact array-based data representation.
   - Library code based on stream fusion automatically reduces copying in
   your application, compared to a more naive library.
   - The lazy text type supports streaming of data much larger than RAM.

Features of text-icu:

   -
   - Locale sensitive case mapping.
   - [NEW] Language sensitive text boundary analysis.
   - Text normalization. (What is normalization?
   http://unicode.org/faq/normalization.html)
   - [NEW] Access to the Unicode Character Database.
   - Locale sensitive string collation.
   - Conversion to and from a huge number of native encodings.
   - Efficient comparison of ByteString and Text.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Bryan O'Sullivan
On Tue, Sep 14, 2010 at 11:21 AM, Edward Z. Yang ezy...@mit.edu wrote:


 Pure code can always be safely asynchronously interrupted (even code
 using state like the ST monad), and IO code can be made to interact
 correctly with thread termination simply by using appropriate bracketing
 functions that would handle normal IO exceptions.


Ertugrul's advice is still correct. I'd wager there are very few concurrent
applications that could survive a killThread without disaster. People simply
don't write or test code with that in mind, and even when they do, it's more
likely than not to be wrong.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Cleaning up threads

2010-09-14 Thread Bryan O'Sullivan
On Tue, Sep 14, 2010 at 12:04 PM, Gregory Collins
g...@gregorycollins.netwrote:

 That's surprising to me -- this is how we kill the Snap webserver
 (killThread the controlling thread...).


It's one thing to design code to work that way and test it all the time, but
it would be quite another to claim that killThread makes sense outside of
that very narrow context.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Text performance problem

2010-09-13 Thread Bryan O'Sullivan
On Mon, Sep 13, 2010 at 3:26 AM, Petr Prokhorenkov
prokhoren...@gmail.comwrote:

 I really didn't expect mapAccumL to have quadratic complexity. Thank you a
 lot for the fix!


No problem. By the way, in my benchmarks, mapAccumL on Text is now faster
than on ByteString :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Data.Text performance problem

2010-09-12 Thread Bryan O'Sullivan
On Sun, Sep 12, 2010 at 12:23 PM, Petr Prokhorenkov
prokhoren...@gmail.comwrote:

 I experienced a following problem while dealing with some text processing.


Thanks for the report and the test case. There's nothing wrong with your
code - read on for details.

You ran into one of the few functions in Data.Text that I copied straight
over from the list implementation due to it not being used often.
Unfortunately, that implementation constructs a new Text value (using cons)
on every iteration through the loop, and as you might expect that's very
slow even on tiny inputs, as it has quadratic behaviour.

I've rewritten both strict and lazy mapAccumL and mapAccumR to use as much
of the stream fusion machinery as possible. (By the way, there's an
interesting fact behind why those functions started out life as they did:
you can't write mapAccum functions using only stream machinery, due to their
types, and the strict code is more work to write if you can't use the stream
machinery. In the early days it just wasn't worth writing the more complex
variants of them, as I had more pressing performance concerns at the time.)

Where the old version of mapAccumL caused your test case to take 5 seconds
to process an 11KB file (ouch!), with the rewritten version, your code can
process an 81MB file in the same amount of time, without any changes to your
code, and that O(n^2) behaviour is gone :-)

text 0.8.1.0 is now up on hackage, with the fix included. Enjoy!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANNOUNCE: text-icu 0.4.0.0

2010-09-10 Thread Bryan O'Sullivan
The text-icu library is the more practical cousin to the text library,
implementing a myriad of Unicode-related functionality that is not yet
otherwise available in Haskell. It is implemented as bindings to the widely
used ICU library.

http://hackage.haskell.org/package/text-icu

Features:

   - Locale sensitive case mapping.
   - Text normalization. (What is normalization?
   http://unicode.org/faq/normalization.html)
   - [NEW] Locale sensitive string collation.
   - Conversion to and from a huge number of native encodings.
   - [NEW] Efficient comparison of ByteString and Text.

The library is thoroughly documented, and most interfaces are pure and easy
to use.

Look for further releases over the coming weeks as I complete the ICU
integration.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] PSA: using MySQL from Haskell programs

2010-09-07 Thread Bryan O'Sullivan
If you are using HDBC-mysql or HDBC-odbc to access MySQL databases, you may
have run into problems with your programs failing due to connection errors.
In this blog posting, I describe what's happening and how to work around it:

http://www.serpentine.com/blog/2010/09/04/dealing-with-fragile-c-libraries-e-g-mysql-from-haskell/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: Form a haskell.org committee

2010-09-07 Thread Bryan O'Sullivan
On Sun, Sep 5, 2010 at 9:34 PM, Jason Dagit da...@codersbase.com wrote:

 The darcs project uses the Software Freedom Conservancy as a sort of
 legal entity to hold on to funds and also to help in case anyone takes
 legal action against darcs or darcs needs to take legal action.


I have only the highest praise for the Software Freedom Conservancy folks.
They are smart, capabale, and very accommodating.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] ANNOUNCE: text 0.8.0.0, fast Unicode text support

2010-09-07 Thread Bryan O'Sullivan
On Wed, Sep 1, 2010 at 12:29 PM, Daniel Fischer daniel.is.fisc...@web.dewrote:

 I'm on Linux. I guess that's another point in favour of it:)
 Do you happen to know why it's slower on a Mac?


I'd guess because of something to do with the system iconv.


 So I tentatively believe most of the difference is spent doing the
 replacements.


I have a Replace.hs benchmark in the main text repo, just to be sure we're
talking about the same thing. Factoring out the time spent on I/O, with GHC
HEAD, my replace code takes twice the space and time of that in the
stringsearch package. Given that the space involved is just 121KB maximum
residency while processing a 124MB file, I'm not concerned about it. And the
time required isn't a bad place to start from, I think.

By the way, as this implies, I can't reproduce your space behaviour at all.

I can now say more. Looking at Data.Text.Lazy.replace,

 replace s d = intercalate d . split s

, I also got a space leak with that for BS.Lazy's intercalate and
 stringsearch's split.


How did you observe the space leak? Looking at -hT charted with hp2ps shows
me nothing, and the program executes in constant space regardless of input
size.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Laziness bug in Data.List.intersperse (was: ANNOUNCE: text 0.8.0.0, fast Unicode text support)

2010-09-04 Thread Bryan O'Sullivan
On Wed, Sep 1, 2010 at 1:00 PM, Daniel Fischer daniel.is.fisc...@web.dewrote:

 I'm not keen on subscribing to libraries@ to follow the official proposal
 process, any takers?


I'll take it up.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


  1   2   3   4   5   >