Re: [Haskell-cafe] attoparsec and backtracking

2013-03-19 Thread oleg

Wren Thornton wrote:
 I had some similar issues recently. The trick is figuring out how to
 convince attoparsec to commit to a particular alternative. For example,
 consider the grammar: A (B A)* C; where if the B succeeds then we want to
 commit to parsing an A (and if it fails then return A's error, not C's).

Indeed. Consider the following (greatly simplified) fragment from the
OCaml grammar

| let; r = opt_rec; bi = binding; in;
   x = expr LEVEL ; -
| function; a = match_case -
| if; e1 = SELF; then; e2 = expr LEVEL top;
  else; e3 = expr LEVEL top -
...
| false - 
| true  - 

It would be bizarre if the parser -- upon seeing if but not finding
then -- would've reported the error that `found if when true was
expected'. Many people would think that when the parser comes across
if, it should commit to parsing the conditional. And if it fails later, it
should report the error with the conditional, rather than trying to
test how else the conditional cannot be parsed. This is exactly the
intuition of pattern matching. For example, given

 foo (if:t) = case t of
  (e:then:_) - e
 foo _ = 

we expect that 
foo [if,false,false]
will throw an exception rather than return the empty string. If the
pattern has matched, we are committed to the corresponding
branch. Such an intuition ought to apply to parsing -- and indeed it
does. The OCaml grammar above was taken from the camlp4 code. Camlp4
parsers

http://caml.inria.fr/pub/docs/tutorial-camlp4/tutorial002.html#toc6

do pattern-matching on a stream, for example
 # let rec expr =
 parser
   [ 'If; x = expr; 'Then; y = expr; 'Else; z = expr ] - if
 | [ 'Let; 'Ident x; 'Equal; x = expr; 'In; y = expr ] - let

and raise two different sort of exceptions. A parser raises
Stream.Failure if it failed on the first element of the stream (in the
above case, if the stream contains neither If nor Let). If the parser
successfully consumed the first element but failed later, a different
Stream.Error is thrown. Although Camlp4 has many detractors, even they
admit that the parsing technology by itself is surprisingly powerful,
and produces error messages that are oftentimes better than those by
the yacc-like, native OCaml parser. Camlp4 parsers are used
extensively in Coq.

The idea of two different failures may help in the case of attoparsec
or parsec. Regular parser failure initiates backtracking. If we wish
to terminate the parser, we should raise the exception (and cut the
rest of the choice points). Perhaps the could be a combinator `commit'
that converts a failure to the exception. In the original example
A (B A)* C we would use it as A (B (commit A))* C.



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


Re: [Haskell-cafe] Need some advice around lazy IO

2013-03-19 Thread Konstantin Litvinenko

On 03/19/2013 07:12 AM, Edward Kmett wrote:

Konstantin,

Please allow me to elaborate on Dan's point -- or at least the point
that I believe that Dan is making.

Using,

let bug = Control.DeepSeq.rnf str `seq` fileContents2Bug str


or ($!!)will create a value that *when forced* cause the rnfto occur.

As you don't look at buguntil much later this causes the same problem as
before!



Yes. You (and Dan) are totally right. 'Let' just bind expression, not 
evaluating it. Dan's evaluate trick force rnf to run before hClose. As I 
said - it's tricky part especially for newbie like me :)




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


Re: [Haskell-cafe] Need some advice around lazy IO

2013-03-19 Thread Kim-Ee Yeoh
On Tue, Mar 19, 2013 at 2:01 PM, Konstantin Litvinenko
to.darkan...@gmail.com wrote:
 Yes. You (and Dan) are totally right. 'Let' just bind expression, not
 evaluating it. Dan's evaluate trick force rnf to run before hClose. As I
 said - it's tricky part especially for newbie like me :)

To place this in perspective, one only needs to descend one or two
more layers before the semantics starts confusing even experts.

Whereas the difference between seq and evaluate shouldn't be too hard
to grasp, that between evaluate and (return $!) is considerably more
subtle, as Edward Yang notified us 10 days ago. See the thread titled
To seq or not to seq.

-- Kim-Ee

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


Re: [Haskell-cafe] Fwd: Now Accepting Applications for Mentoring Organizations for GSoC 2013

2013-03-19 Thread Oliver Charles

On 03/18/2013 08:49 PM, Johan Tibell wrote:

[bcc: hask...@haskell.org mailto:hask...@haskell.org]

We should make sure that we apply for Google Summer of Code this year 
as well. It's been very successful in the previous year, where we have 
gotten several projects funded every year.
Definitely - plus it means I get to meet other Haskell'ers at the mentor 
summit ;)


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


Re: [Haskell-cafe] Specialized Computer Architecture - A Question

2013-03-19 Thread Simon Farnsworth
OWP wrote:

 Ironically, you made an interesting point on how Moore's Law created
 the on chip real estate that made specialized machines possible.  As
 transistor sizing shrinks and die sizes increase, more and more real
 estate should now be available for usage.  Oddly, what destroyed
 specialized machines in the past seemed to be the same cause in
 reviving it from the dead.
 
 The ARM Jazelle interface - I'm not familiar with it's but it's got me
 curious.  Has there been any though (even in the most lighthearted
 discussions) on what a physical Haskell Machine could look like?
 Mainly, what could be left to compile to the stock architecture and
 what could be sent out to more specialized areas?
 
You might be interested in looking at the Reduceron - 
http://www.cs.york.ac.uk/fp/reduceron/ - it was an FPGA-based effort to 
design a CPU explicitly for a Haskell-like language.

-- 
Simon Farnsworth


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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Konstantin Litvinenko

On 03/18/2013 02:14 PM, Gregory Collins wrote:

Put a bang pattern on your accumulator in go. Since the value is not
demanded until the end of the program, you're actually just building up
a huge space leak there.


Fixed that


Secondly, unconsing from the lazy bytestring will cause a lot of
allocation churn in the garbage collector -- each byte read in the input
forces the creation of a new L.ByteString, which is many times larger.


Nope. L.ByteString is created along with strict ByteString but content 
not copied. And, in fact, that not a problem. The problem is that GHC 
unable to optimize constantly changing state in State monad. I don't 
know is it posible or not and if it is than what should I do to allow 
such optimization.


import Control.Monad.State.Strict

data S6 = S6 Int Int

main_6 = do
let r = evalState go (S6 1 0)
print r
  where
go = do
(S6 i a) - get
if (i == 0) then return a else put (S6 (i - 1) (a + i))  go

main_7 = do
let r = go (S6 1 0)
print r
  where
go (S6 i a)
| i == 0 = a
| otherwise = go $ S6 (i - 1) (a + i)

main = main_7

If I run main_6 I get constant allocations. If I run main_7 I get no 
allocations.


Does anybody know how to overcome this inefficiency?


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


Re: [Haskell-cafe] Announcement - HGamer3D - 0.2.1 - featuring FRP based GUI and more

2013-03-19 Thread Heinrich Apfelmus

Peter Althainz wrote:

Dear All,

I'm happy to announce release 0.2.1 of HGamer3D, the game engine with 
Haskell API, featuring FRP based API and FRP based GUI. The new FRP API 
is based on the netwire package. Currently only available on Windows: 
http://www.hgamer3d.org.


Nice work!

Of course, I have to ask: what influenced your choice of FRP library in 
favor of  netwire  instead of  reactive-banana ?



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Don Stewart
Just for fun. Here's some improvements. about 6x faster.
I'd be interested to see what io-streams could do on this.

Using a 250M test file.

-- strict state monad and bang patterns on the uncons and accumulator
argument:

$ time ./A
4166680
./A  8.42s user 0.57s system 99% cpu 9.037 total

-- just write a loop

$ time ./A
4166680
./A  3.84s user 0.26s system 99% cpu 4.121 total

-- switch to Int

$ time ./A
4166680
./A  1.89s user 0.23s system 99% cpu 2.134 total

-- custom isSpace function

$ time ./A
4166680
./A  1.56s user 0.24s system 99% cpu 1.808 total

-- mmap IO

$ time ./A
4166680
./A  1.54s user 0.09s system 99% cpu 1.636 total

Here's the final program:


{-# LANGUAGE BangPatterns #-}

import qualified Data.ByteStringas S
import qualified Data.ByteString.Lazy.Char8 as L
import System.IO.Posix.MMap.Lazy

main = do
f - unsafeMMapFile test.txt
print $ go 0 f
  where
go :: Int - L.ByteString - Int
go !a !s = case L.uncons s of
Nothing - a
Just (x,xs) | isSpaceChar8 x - go (a+1) xs
| otherwise  - go a xs

isSpaceChar8 c = c == '\n'|| c == ' '
{-# INLINE isSpaceChar8 #-}


On Mon, Mar 18, 2013 at 8:53 AM, Konstantin Litvinenko 
to.darkan...@gmail.com wrote:

 Hi All!

 I tune my toy project for performance and hit the wall on simple, in
 imperative world, task. Here is the code that model what I'm trying to
 achieve

 import qualified Data.ByteString.Lazy as L
 import Data.Word8(isSpace)
 import Data.Word
 import Control.Monad.State

 type Stream = State L.ByteString

 get_byte :: Stream (Maybe Word8)
 get_byte = do
 s - get
 case L.uncons s of
 Nothing - return Nothing
 Just (x, xs) - put xs  return (Just x)

 main = do
 f - L.readFile test.txt
 let r = evalState count_spaces f
 print r
   where
 count_spaces = go 0
   where
 go a = do
 x - get_byte
 case x of
 Just x' -  if isSpace x' then go (a + 1) else go a
 Nothing - return a

 It takes the file and count spaces, in imperative way, consuming bytes one
 by one. The problem is: How to rewrite this to get rid of constant
 allocation of state but still working with stream of bytes? I can rewrite
 this as one-liner L.foldl, but that doesn't help me in any way to optimize
 my toy project where all algorithms build upon consuming stream of bytes.

 PS. My main lang is C++ over 10 years and I only learn Haskell :)


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Don Stewart
Oh, I forgot the technique of inlining the lazy bytestring chunks, and
processing each chunk seperately.

$ time ./fast
4166680
./fast  1.25s user 0.07s system 99% cpu 1.325 total

Essentially inline Lazy.foldlChunks and specializes is (the inliner should
really get that).
And now we have a nice unboxed inner loop, which llvm might spot:

$ ghc -O2 -funbox-strict-fields fast.hs  --make -fllvm
$ time ./fast
4166680
./fast  1.07s user 0.06s system 98% cpu *1.146 total*

So about 8x faster. Waiting for some non-lazy bytestring benchmarks... :)

{-# LANGUAGE BangPatterns #-}

import Data.ByteString.Internal
import Data.ByteString.Unsafe
import qualified Data.ByteString.Char8  as S
import qualified Data.ByteString.Lazy.Char8 as L
import qualified Data.ByteString.Lazy.Internal as L
import System.IO.Posix.MMap.Lazy

main = do
f - unsafeMMapFile test.txt
print . new 0 $ L.toChunks f

new :: Int - [ByteString] - Int
new i [] = i
new i (x:xs) = new (add i x) xs

-- jump into the fast path
{-# INLINE add #-}
add :: Int - ByteString - Int
add !i !s | S.null s   = i
  | isSpace' x = add (i+1) xs
  | otherwise  = add i xs
  where T x xs = uncons s

data T = T !Char ByteString

uncons s = T (w2c (unsafeHead s)) (unsafeTail s)

isSpace' c = c == '\n'|| c == ' '
{-# INLINE isSpace' #-}




On Tue, Mar 19, 2013 at 7:36 PM, Don Stewart don...@gmail.com wrote:

 Just for fun. Here's some improvements. about 6x faster.
 I'd be interested to see what io-streams could do on this.

 Using a 250M test file.

 -- strict state monad and bang patterns on the uncons and accumulator
 argument:

 $ time ./A
 4166680
 ./A  8.42s user 0.57s system 99% cpu 9.037 total

 -- just write a loop

 $ time ./A
 4166680
 ./A  3.84s user 0.26s system 99% cpu 4.121 total

 -- switch to Int

 $ time ./A
 4166680
 ./A  1.89s user 0.23s system 99% cpu 2.134 total

 -- custom isSpace function

 $ time ./A
 4166680
 ./A  1.56s user 0.24s system 99% cpu 1.808 total

 -- mmap IO

 $ time ./A
 4166680
 ./A  1.54s user 0.09s system 99% cpu 1.636 total

 Here's the final program:


 {-# LANGUAGE BangPatterns #-}

 import qualified Data.ByteStringas S
 import qualified Data.ByteString.Lazy.Char8 as L
 import System.IO.Posix.MMap.Lazy

 main = do
 f - unsafeMMapFile test.txt
 print $ go 0 f
   where
 go :: Int - L.ByteString - Int
 go !a !s = case L.uncons s of
 Nothing - a
 Just (x,xs) | isSpaceChar8 x - go (a+1) xs
 | otherwise  - go a xs

 isSpaceChar8 c = c == '\n'|| c == ' '
 {-# INLINE isSpaceChar8 #-}


 On Mon, Mar 18, 2013 at 8:53 AM, Konstantin Litvinenko 
 to.darkan...@gmail.com wrote:

 Hi All!

 I tune my toy project for performance and hit the wall on simple, in
 imperative world, task. Here is the code that model what I'm trying to
 achieve

 import qualified Data.ByteString.Lazy as L
 import Data.Word8(isSpace)
 import Data.Word
 import Control.Monad.State

 type Stream = State L.ByteString

 get_byte :: Stream (Maybe Word8)
 get_byte = do
 s - get
 case L.uncons s of
 Nothing - return Nothing
 Just (x, xs) - put xs  return (Just x)

 main = do
 f - L.readFile test.txt
 let r = evalState count_spaces f
 print r
   where
 count_spaces = go 0
   where
 go a = do
 x - get_byte
 case x of
 Just x' -  if isSpace x' then go (a + 1) else go a
 Nothing - return a

 It takes the file and count spaces, in imperative way, consuming bytes
 one by one. The problem is: How to rewrite this to get rid of constant
 allocation of state but still working with stream of bytes? I can rewrite
 this as one-liner L.foldl, but that doesn't help me in any way to optimize
 my toy project where all algorithms build upon consuming stream of bytes.

 PS. My main lang is C++ over 10 years and I only learn Haskell :)


 __**_
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe



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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Konstantin Litvinenko

On 03/19/2013 10:32 PM, Don Stewart wrote:

Oh, I forgot the technique of inlining the lazy bytestring chunks, and
processing each chunk seperately.

$ time ./fast
4166680
./fast  1.25s user 0.07s system 99% cpu 1.325 total

Essentially inline Lazy.foldlChunks and specializes is (the inliner
should really get that).
And now we have a nice unboxed inner loop, which llvm might spot:

$ ghc -O2 -funbox-strict-fields fast.hs  --make -fllvm
$ time ./fast
4166680
./fast  1.07s user 0.06s system 98% cpu *1.146 total*

So about 8x faster. Waiting for some non-lazy bytestring benchmarks... :)


Thanks Don, but after some investigation I came to conclusion that 
problem is in State monad


{-# LANGUAGE BangPatterns #-}

import Control.Monad.State.Strict

data S6 = S6 !Int !Int

main_6 = do
let r = evalState go (S6 1 0)
print r
  where
go = do
(S6 i a) - get
if (i == 0) then return a else (put (S6 (i - 1) (a + i)))  go

main_7 = do
let r = go (S6 1 0)
print r
  where
go (S6 i a)
| i == 0 = a
| otherwise = go $ S6 (i - 1) (a + i)

main = main_6

main_6 doing constant allocations while main_7 run in constant space. 
Can you suggest something that improve situation? I don't want to 
manually unfold all my code that I want to be fast :(.


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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Nicolas Trangez
On Tue, 2013-03-19 at 20:32 +, Don Stewart wrote:
 Oh, I forgot the technique of inlining the lazy bytestring chunks, and
 processing each chunk seperately.
 
 $ time ./fast
 4166680
 ./fast  1.25s user 0.07s system 99% cpu 1.325 total
 
 Essentially inline Lazy.foldlChunks and specializes is (the inliner should
 really get that).
 And now we have a nice unboxed inner loop, which llvm might spot:
 
 $ ghc -O2 -funbox-strict-fields fast.hs  --make -fllvm
 $ time ./fast
 4166680
 ./fast  1.07s user 0.06s system 98% cpu *1.146 total*
 
 So about 8x faster. Waiting for some non-lazy bytestring benchmarks... :)

You could try something like this using Conduit:

{-# LANGUAGE BangPatterns #-}
module Main (main) where

import Data.Conduit
import qualified Data.Conduit.List as L
import qualified Data.Conduit.Binary as B
import qualified Data.ByteString.Char8 as BS8

main :: IO ()
main = print = runResourceT (
B.sourceFile filename $$ L.fold (\(!a) (!b) - a + BS8.count ' ' b)
(0 :: Int))
  where
filename = ...

Nicolas

 
 {-# LANGUAGE BangPatterns #-}
 
 import Data.ByteString.Internal
 import Data.ByteString.Unsafe
 import qualified Data.ByteString.Char8  as S
 import qualified Data.ByteString.Lazy.Char8 as L
 import qualified Data.ByteString.Lazy.Internal as L
 import System.IO.Posix.MMap.Lazy
 
 main = do
 f - unsafeMMapFile test.txt
 print . new 0 $ L.toChunks f
 
 new :: Int - [ByteString] - Int
 new i [] = i
 new i (x:xs) = new (add i x) xs
 
 -- jump into the fast path
 {-# INLINE add #-}
 add :: Int - ByteString - Int
 add !i !s | S.null s   = i
   | isSpace' x = add (i+1) xs
   | otherwise  = add i xs
   where T x xs = uncons s
 
 data T = T !Char ByteString
 
 uncons s = T (w2c (unsafeHead s)) (unsafeTail s)
 
 isSpace' c = c == '\n'|| c == ' '
 {-# INLINE isSpace' #-}
 
 
 
 
 On Tue, Mar 19, 2013 at 7:36 PM, Don Stewart don...@gmail.com wrote:
 
  Just for fun. Here's some improvements. about 6x faster.
  I'd be interested to see what io-streams could do on this.
 
  Using a 250M test file.
 
  -- strict state monad and bang patterns on the uncons and accumulator
  argument:
 
  $ time ./A
  4166680
  ./A  8.42s user 0.57s system 99% cpu 9.037 total
 
  -- just write a loop
 
  $ time ./A
  4166680
  ./A  3.84s user 0.26s system 99% cpu 4.121 total
 
  -- switch to Int
 
  $ time ./A
  4166680
  ./A  1.89s user 0.23s system 99% cpu 2.134 total
 
  -- custom isSpace function
 
  $ time ./A
  4166680
  ./A  1.56s user 0.24s system 99% cpu 1.808 total
 
  -- mmap IO
 
  $ time ./A
  4166680
  ./A  1.54s user 0.09s system 99% cpu 1.636 total
 
  Here's the final program:
 
 
  {-# LANGUAGE BangPatterns #-}
 
  import qualified Data.ByteStringas S
  import qualified Data.ByteString.Lazy.Char8 as L
  import System.IO.Posix.MMap.Lazy
 
  main = do
  f - unsafeMMapFile test.txt
  print $ go 0 f
where
  go :: Int - L.ByteString - Int
  go !a !s = case L.uncons s of
  Nothing - a
  Just (x,xs) | isSpaceChar8 x - go (a+1) xs
  | otherwise  - go a xs
 
  isSpaceChar8 c = c == '\n'|| c == ' '
  {-# INLINE isSpaceChar8 #-}
 
 
  On Mon, Mar 18, 2013 at 8:53 AM, Konstantin Litvinenko 
  to.darkan...@gmail.com wrote:
 
  Hi All!
 
  I tune my toy project for performance and hit the wall on simple, in
  imperative world, task. Here is the code that model what I'm trying to
  achieve
 
  import qualified Data.ByteString.Lazy as L
  import Data.Word8(isSpace)
  import Data.Word
  import Control.Monad.State
 
  type Stream = State L.ByteString
 
  get_byte :: Stream (Maybe Word8)
  get_byte = do
  s - get
  case L.uncons s of
  Nothing - return Nothing
  Just (x, xs) - put xs  return (Just x)
 
  main = do
  f - L.readFile test.txt
  let r = evalState count_spaces f
  print r
where
  count_spaces = go 0
where
  go a = do
  x - get_byte
  case x of
  Just x' -  if isSpace x' then go (a + 1) else go a
  Nothing - return a
 
  It takes the file and count spaces, in imperative way, consuming bytes
  one by one. The problem is: How to rewrite this to get rid of constant
  allocation of state but still working with stream of bytes? I can rewrite
  this as one-liner L.foldl, but that doesn't help me in any way to optimize
  my toy project where all algorithms build upon consuming stream of bytes.
 
  PS. My main lang is C++ over 10 years and I only learn Haskell :)
 
 
  __**_
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/**mailman/listinfo/haskell-cafehttp://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



___

Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Konstantin Litvinenko

On 03/19/2013 10:53 PM, Nicolas Trangez wrote:

On Tue, 2013-03-19 at 20:32 +, Don Stewart wrote:

So about 8x faster. Waiting for some non-lazy bytestring benchmarks... :)


You could try something like this using Conduit:

{-# LANGUAGE BangPatterns #-}
module Main (main) where

import Data.Conduit
import qualified Data.Conduit.List as L
import qualified Data.Conduit.Binary as B
import qualified Data.ByteString.Char8 as BS8

main :: IO ()
main = print = runResourceT (
 B.sourceFile filename $$ L.fold (\(!a) (!b) - a + BS8.count ' ' b)
(0 :: Int))
   where
 filename = ...


Please stops counting spaces! :) It was a MODEL that demonstrates 
constant allocation of state when I used State monad. That's the 
*problem*. I mention in my first email that I do know how to count 
spaces using one-line L.foldl with no allocations at all :).



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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Peter Simons
Don Stewart don...@gmail.com writes:

  Here's the final program: [...]

Here is a version of the program that is just as fast:

  import Prelude hiding ( getContents, foldl )
  import Data.ByteString.Char8

  countSpace :: Int - Char - Int
  countSpace i c | c == ' ' || c == '\n' = i + 1
 | otherwise = i

  main :: IO ()
  main = getContents = print . foldl countSpace 0

Generally speaking, I/O performance is not about fancy low-level system
features, it's about having a proper evaluation order:

 | $ ghc --make -O2 -funbox-strict-fields test1  time ./test1
 | 37627064
 |
 | real 0m0.381s
 | user 0m0.356s
 | sys  0m0.023s

Versus:

 | $ ghc --make -O2 -funbox-strict-fields test2  time ./test2 test.txt
 | Linking test2 ...
 | 37627064
 |
 | real 0m0.383s
 | user 0m0.316s
 | sys  0m0.065s

Using this input file stored in /dev/shm:

 | $ ls -l test.txt 
 | -rw-r--r-- 1 simons users 208745650 Mar 19 21:40 test.txt

Take care,
Peter


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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Don Stewart
This isn't a valid entry -- it uses strict IO (so allocates O(n) space) and
reads from standard input, which pretty much swamps the interesting
constant factors with buffered IO overhead.

Compare your program (made lazy) on lazy bytestrings using file IO:

import Prelude hiding ( readFile, foldl )
import Data.ByteString.Lazy.Char8

countSpace :: Int - Char - Int
countSpace i c | c == ' ' || c == '\n' = i + 1
   | otherwise = i

main :: IO ()
main = readFile test.txt = print . foldl countSpace 0


Against my earlier optimized one (that manually specializes and does other
tricks).


$ time ./C
4166680
./C  1.49s user 0.42s system 82% cpu 2.326 total

$ time ./fast
4166680
./fast  1.05s user 0.11s system 96% cpu 1.201 total


The optimized one is twice as fast. You can write the same program on lists
, and it also runs in constant space but completes 32s instead  of 1.3

Constant factors matter.

On Tue, Mar 19, 2013 at 9:03 PM, Peter Simons sim...@cryp.to wrote:

 Don Stewart don...@gmail.com writes:

   Here's the final program: [...]

 Here is a version of the program that is just as fast:

   import Prelude hiding ( getContents, foldl )
   import Data.ByteString.Char8

   countSpace :: Int - Char - Int
   countSpace i c | c == ' ' || c == '\n' = i + 1
  | otherwise = i

   main :: IO ()
   main = getContents = print . foldl countSpace 0

 Generally speaking, I/O performance is not about fancy low-level system
 features, it's about having a proper evaluation order:

  | $ ghc --make -O2 -funbox-strict-fields test1  time ./test1
  | 37627064
  |
  | real 0m0.381s
  | user 0m0.356s
  | sys  0m0.023s

 Versus:

  | $ ghc --make -O2 -funbox-strict-fields test2  time ./test2 test.txt
  | Linking test2 ...
  | 37627064
  |
  | real 0m0.383s
  | user 0m0.316s
  | sys  0m0.065s

 Using this input file stored in /dev/shm:

  | $ ls -l test.txt
  | -rw-r--r-- 1 simons users 208745650 Mar 19 21:40 test.txt

 Take care,
 Peter


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

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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Konstantin Litvinenko

On 03/19/2013 10:49 PM, Konstantin Litvinenko wrote:

{-# LANGUAGE BangPatterns #-}

import Control.Monad.State.Strict

data S6 = S6 !Int !Int

main_6 = do
 let r = evalState go (S6 1 0)
 print r
   where
 go = do
 (S6 i a) - get
 if (i == 0) then return a else (put (S6 (i - 1) (a + i)))  go

main_7 = do
 let r = go (S6 1 0)
 print r
   where
 go (S6 i a)
 | i == 0 = a
 | otherwise = go $ S6 (i - 1) (a + i)

main = main_6

main_6 doing constant allocations while main_7 run in constant space.
Can you suggest something that improve situation? I don't want to
manually unfold all my code that I want to be fast :(.


Correction - they both run in constant space, that's not a problem. The 
problem is main_6 doing constant allocation/destroying and main_7 doesn't.



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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Peter Simons
Hi Don,

  Compare your program (made lazy) on lazy bytestrings using file IO: [...]

if I make those changes, the program runs even faster than before:

  module Main ( main ) where

  import Prelude hiding ( foldl, readFile )
  import Data.ByteString.Lazy.Char8

  countSpace :: Int - Char - Int
  countSpace i c | c == ' ' || c == '\n' = i + 1
 | otherwise = i

  main :: IO ()
  main = readFile test.txt = print . foldl countSpace 0

This gives

 | $ ghc --make -O2 -funbox-strict-fields test1  time ./test1
 | 37627064
 |
 | real0m0.375s
 | user0m0.346s
 | sys 0m0.028s

versus:

 | $ ghc --make -O2 -funbox-strict-fields test2  time ./test2
 | 37627064
 |
 | real0m0.324s
 | user0m0.299s
 | sys 0m0.024s

Whether getFile or getContents is used doesn't seem to make difference.

Take care,
Peter

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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Don Stewart
Oh I see what you're doing ... Using this input file stored in /dev/shm

So not measuring the IO performance at all. :)
On Mar 19, 2013 9:27 PM, Peter Simons sim...@cryp.to wrote:

 Hi Don,

   Compare your program (made lazy) on lazy bytestrings using file IO:
 [...]

 if I make those changes, the program runs even faster than before:

   module Main ( main ) where

   import Prelude hiding ( foldl, readFile )
   import Data.ByteString.Lazy.Char8

   countSpace :: Int - Char - Int
   countSpace i c | c == ' ' || c == '\n' = i + 1
  | otherwise = i

   main :: IO ()
   main = readFile test.txt = print . foldl countSpace 0

 This gives

  | $ ghc --make -O2 -funbox-strict-fields test1  time ./test1
  | 37627064
  |
  | real0m0.375s
  | user0m0.346s
  | sys 0m0.028s

 versus:

  | $ ghc --make -O2 -funbox-strict-fields test2  time ./test2
  | 37627064
  |
  | real0m0.324s
  | user0m0.299s
  | sys 0m0.024s

 Whether getFile or getContents is used doesn't seem to make difference.

 Take care,
 Peter

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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Peter Simons
Hi Don,

  Using this input file stored in /dev/shm
 
  So not measuring the IO performance at all. :)

of course the program measures I/O performance. It just doesn't measure
the speed of the disk.

Anyway, a highly optimized benchmark such as the one you posted is
eventually going to beat one that's not as highly optimized. I think
no-one disputes that fact.

I was merely trying to point out that a program which encodes its
evaluation order properly is going to be reasonably fast without any
further optimizations.

Take care,
Peter

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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Don Stewart
I guess the optimizations that went into making lazy bytestring IO fast (on
disks) are increasingly irrelevant as SSDs take over.
On Mar 19, 2013 9:49 PM, Peter Simons sim...@cryp.to wrote:

 Hi Don,

   Using this input file stored in /dev/shm
  
   So not measuring the IO performance at all. :)

 of course the program measures I/O performance. It just doesn't measure
 the speed of the disk.

 Anyway, a highly optimized benchmark such as the one you posted is
 eventually going to beat one that's not as highly optimized. I think
 no-one disputes that fact.

 I was merely trying to point out that a program which encodes its
 evaluation order properly is going to be reasonably fast without any
 further optimizations.

 Take care,
 Peter

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


[Haskell-cafe] package show needs QuickCheck2.6?

2013-03-19 Thread Johannes Waldmann
Hi, I noticed that compilation of mueval (recent: 0.8.2) breaks 
because show (0.5) cannot be built: 
it seems the type of Failure changed in QuickCheck (from 2.5 to 2.6).
The build succeeds with --constraint 'QuickCheck2.6' .



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


Re: [Haskell-cafe] Streaming bytes and performance

2013-03-19 Thread Branimir Maksimovic


 To: haskell-cafe@haskell.org
 From: to.darkan...@gmail.com
 Date: Tue, 19 Mar 2013 23:27:09 +0200
 Subject: Re: [Haskell-cafe] Streaming bytes and performance
 
 On 03/19/2013 10:49 PM, Konstantin Litvinenko wrote:
  {-# LANGUAGE BangPatterns #-}
 
  import Control.Monad.State.Strict
 
  data S6 = S6 !Int !Int
 
  main_6 = do
   let r = evalState go (S6 1 0)
   print r
 where
   go = do
   (S6 i a) - get
   if (i == 0) then return a else (put (S6 (i - 1) (a + i)))  go
 
  main_7 = do
   let r = go (S6 1 0)
   print r
 where
   go (S6 i a)
   | i == 0 = a
   | otherwise = go $ S6 (i - 1) (a + i)
 
  main = main_6
 
  main_6 doing constant allocations while main_7 run in constant space.
  Can you suggest something that improve situation? I don't want to
  manually unfold all my code that I want to be fast :(.
Your problem is that main_6 thunks 'i' and 'a' .If you write (S6 !i !a) - 
getthan there is no problem any more...
 
 Correction - they both run in constant space, that's not a problem. The 
 problem is main_6 doing constant allocation/destroying and main_7 doesn't.
No main_6 does not runs in constant space if you dont use bang patterns...

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


Re: [Haskell-cafe] Associated types for number coercion

2013-03-19 Thread Johan Tibell
On Tue, Mar 19, 2013 at 3:58 PM, Christopher Done chrisd...@gmail.comwrote:

 From the paper Fun with Type Funs, it's said:

  One compelling use of such type functions is to make type
  coercions implicit, especially in arithmetic. Suppose we want to be able
 to
  write add a b to add two numeric values a and b even if one is an Integer
  and the other is a Double (without writing fromIntegral explicitly).

 And then an Add class is defined which can dispatch at the type-level
 to appropriate functions which resolve two types into one, with a
 catch-all case for Num.

 Has anyone put this into a package, for all common arithmetic
 operations? I would use it. Doing arithmetic stuff in Haskell always
 feels labored because of having constantly convert between number
 types.


I prefer the current way (which is interestingly what Go chose as well).
With implicit casts it's easy to shoot yourself in the foot e.g. when doing
bit-twiddling. These two are different

f :: Word8 - Int - Word32
f w8 n = fromIntegral (w8 `shiftL` n)

f' :: Word8 - Int - Word32
f' w8 n = (fromIntegral w8) `shiftL` n
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Associated types for number coercion

2013-03-19 Thread Christopher Done
(But I get annoyed about having to convert between five string types
(String, Text, lazy Text, ByteString, lazy ByteString), so maybe I'm
just generally more bothered by the whole “not being able to just
write the program” than others.)

On 20 March 2013 00:22, Christopher Done chrisd...@gmail.com wrote:
 On 20 March 2013 00:05, Johan Tibell johan.tib...@gmail.com wrote:
 I prefer the current way (which is interestingly what Go chose as well).
 With implicit casts it's easy to shoot yourself in the foot e.g. when doing
 bit-twiddling.

 I don't think it's an either-or case, though, is it? I would use the
 magic implicitness when I don't care, like all the times I have to
 write fromIntegral because I have an Int here and an Integer there,
 and now I want to use them in a Double calculation, so my code ends up
 littered with fromIntegral, or fi. Elsewhere in the world,
 programmers just write arithmetic. When I would care, like in
 bit-twiddling, I would use the explicit conversions.

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


[Haskell-cafe] Extracting exposed modules from an installed library

2013-03-19 Thread Corentin Dupont
Hi Cafe!
I'm looking for how to extract the exposed modules (as a list of strings)
from an installed library, giving the library name.
I can see some structures in Cabal (InstalledPackageInfo) and some
functions in ghc-pkg.hs in GHC, but nothing readily useable...
Thanks,
Corenti
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Associated types for number coercion

2013-03-19 Thread Conrad Parker
On 20 March 2013 06:58, Christopher Done chrisd...@gmail.com wrote:
 From the paper Fun with Type Funs, it's said:

 One compelling use of such type functions is to make type
 coercions implicit, especially in arithmetic. Suppose we want to be able to
 write add a b to add two numeric values a and b even if one is an Integer
 and the other is a Double (without writing fromIntegral explicitly).

 And then an Add class is defined which can dispatch at the type-level
 to appropriate functions which resolve two types into one, with a
 catch-all case for Num.

 Has anyone put this into a package, for all common arithmetic
 operations? I would use it. Doing arithmetic stuff in Haskell always
 feels labored because of having constantly convert between number
 types.

hmatrix takes this approach with a Mul typeclass for combinations of
Vector and Matrix multiplication, defined for things that can
implement Product (real and Complex Doubles and Floats).

http://hackage.haskell.org/packages/archive/hmatrix/0.14.1.0/doc/html/Numeric-Container.html

I think it'd be interesting for numeric stuff to have implicit
conversion to Double, using a class as you suggest which doesn't
support Integral or bitops.

Conrad.

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


[Haskell-cafe] Does GHC 7.8 make targeting bare metal ARM any easier?

2013-03-19 Thread Jeremy Shaw
There have been at least a couple projects, such as hOp and HaLVM
which attempt to run GHC on the bare metal or something similar.

Both these projects required a substantial set of patches against GHC
to remove dependencies things like POSIX/libc. Due to the highly
invasive nature, they are also highly prone to bitrot.

With GHC 7.8, I believe we will be able to cross-compile to the
Raspberry Pi platform. But, what really appeals to me is going that
extra step and avoiding the OS entirely and running on the bare metal.
Obviously, you give up a lot -- such as drivers, network stacks, etc.
But, there is also a lot of potential to do neat things, and not have
to worry about properly shutting down an embedded linux box.

Also, since the raspberry pi is a very limited, uniform platform,
(compared to general purpose PCs) it is feasible to create network
drivers, etc, because only one chipset needs to be supported.
(Ignoring issues regarding binary blobs, undocumented chipsets, usb
WIFI, etc).

I'm wondering if things are any easier with cross-compilation support
improving. My thought is that less of GHC needs to be tweaked?

- jeremy

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