Re: join points and stream fusion?

2017-04-27 Thread Christian Höner zu Siederdissen
Sorry,

with the addendum, I have constructed a very small example:
https://ghc.haskell.org/trac/ghc/ticket/13623

This is new with ghc 8.2-rc1 and does not show up earlier.

Viele Gruesse,
Christian

* Simon Peyton Jones <simo...@microsoft.com> [28.04.2017 00:35]:
> I'm afraid I don't have enough context to understand this thread.
> 
> Could you offer a concrete example (as small as possible), and explain how to 
> reproduce the problem you are seeing.  Don't forget to give the compiler 
> version you are using, and any libraries you depend on (as few as poss).
> 
> Is this a regression? I.e. did some earlier version of GHC do better on the 
> exact same code?
> 
> Maybe open a Trac ticket.
> 
> Thanks
> 
> Simon
> 
> | -Original Message-
> | From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
> | boun...@haskell.org] On Behalf Of Christian Höner zu Siederdissen
> | Sent: 27 April 2017 23:10
> | To: glasgow-haskell-users@haskell.org
> | Subject: Re: join points and stream fusion?
> | 
> | As an addendum,
> | 
> | I think what causes this is the following. I have a function
> | (|||) xs ys = \lu ij -> xs lu ij Stream.++ ys lu ij xs and ys are two
> | stream-generating functions and (Stream.++) concatenates streams. In the
> | example I have four streams:
> | xs_1 ||| xs_2 ||| xs_3 ||| xs_4
> | 
> | However, here I end up with a join point on (++). Further evidenced (?)
> | by the curious occurance of s1uf4 ... (Left (Left (Left ...))).
> | Additional calls then are (Left (Left (Right ))) and so on.
> | 
> | It would be really good if (|||) is *not* turned into a join point.
> | 
> | Best,
> | Christian
> | 
> | * Christian Höner zu Siederdissen <choe...@bioinf.uni-leipzig.de>
> | [27.04.2017 23:30]:
> | > Dear all,
> | >
> | > have some of you experienced bad code generation in ghc-8.2-rc1 in
> | > combination with stream fusion from the vector package?
> | >
> | > Unfortunately, the problem occurs with ADPfusion code which means no
> | > simple example, but I'm asking because of the following core below.
> | >
> | > In ghc-8.0 I have nice core, here however constructor specialization
> | > has not happened, neither with the Left/Right nor with the SPEC.
> | >
> | > The running time in ghc-8.0 is 2.6 seconds, in rc-1 10.9 seconds.
> | >
> | > Best,
> | > Christian
> | >
> | > joinrec {
> | >   $wfoldlM'_loop2_s1uf4
> | >   $wfoldlM'_loop2_s1uf4 w_s1ueX ww1_s1uf2 w1_s1ueZ
> | > = case w_s1ueX of { __DEFAULT ->
> | >   case w1_s1ueZ of {
> | > Left sa_au90 ->
> | >   case sa_au90 of {
> | > Left sa1_XuNq ->
> | >   case sa1_XuNq of {
> | > Left sa2_XuNe ->
> | >   case sa2_XuNe of {
> | > SL s2_alTo k_alTp ->
> | >   case k_alTp of {
> | > __DEFAULT ->
> | >   jump $wfoldlM'_loop2_s1uf4
> | > SPEC ww1_s1uf2 lvl211_s1IDG;
> | > 1# ->
> | >   jump $wfoldlM'_loop2_s1uf4
> | > SPEC ww1_s1uf2 (Left (Left (Left (SR
> | > s2_alTo
> | >
> | > ___
> | > Glasgow-haskell-users mailing list
> | > Glasgow-haskell-users@haskell.org
> | > https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.h
> | > askell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fglasgow-haskell-users
> | > =02%7C01%7Csimonpj%40microsoft.com%7Cd36333a2218f4c513f5a08d48dba157d%
> | > 7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636289277756070800=
> | > DGsBNjZPuDbpEONyJBOy7BDimCELGHNM1trxjCP5luk%3D=0
> | ___
> | Glasgow-haskell-users mailing list
> | Glasgow-haskell-users@haskell.org
> | https://na01.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.hask
> | ell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fglasgow-haskell-
> | users=02%7C01%7Csimonpj%40microsoft.com%7Cd36333a2218f4c513f5a08d48d
> | ba157d%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636289277756070800
> | ata=DGsBNjZPuDbpEONyJBOy7BDimCELGHNM1trxjCP5luk%3D=0
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


Re: join points and stream fusion?

2017-04-27 Thread Christian Höner zu Siederdissen
As an addendum,

I think what causes this is the following. I have a function
(|||) xs ys = \lu ij -> xs lu ij Stream.++ ys lu ij
xs and ys are two stream-generating functions and (Stream.++)
concatenates streams. In the example I have four streams:
xs_1 ||| xs_2 ||| xs_3 ||| xs_4

However, here I end up with a join point on (++). Further evidenced (?)
by the curious occurance of s1uf4 ... (Left (Left (Left ...))).
Additional calls then are (Left (Left (Right ))) and so on.

It would be really good if (|||) is *not* turned into a join point.

Best,
Christian

* Christian Höner zu Siederdissen <choe...@bioinf.uni-leipzig.de> [27.04.2017 
23:30]:
> Dear all,
> 
> have some of you experienced bad code generation in ghc-8.2-rc1 in
> combination with stream fusion from the vector package?
> 
> Unfortunately, the problem occurs with ADPfusion code which means no
> simple example, but I'm asking because of the following core below.
> 
> In ghc-8.0 I have nice core, here however constructor specialization has
> not happened, neither with the Left/Right nor with the SPEC.
> 
> The running time in ghc-8.0 is 2.6 seconds, in rc-1 10.9 seconds.
> 
> Best,
> Christian
> 
> joinrec {
>   $wfoldlM'_loop2_s1uf4
>   $wfoldlM'_loop2_s1uf4 w_s1ueX ww1_s1uf2 w1_s1ueZ
> = case w_s1ueX of { __DEFAULT ->
>   case w1_s1ueZ of {
> Left sa_au90 ->
>   case sa_au90 of {
> Left sa1_XuNq ->
>   case sa1_XuNq of {
> Left sa2_XuNe ->
>   case sa2_XuNe of {
> SL s2_alTo k_alTp ->
>   case k_alTp of {
> __DEFAULT ->
>   jump $wfoldlM'_loop2_s1uf4
> SPEC ww1_s1uf2 lvl211_s1IDG;
> 1# ->
>   jump $wfoldlM'_loop2_s1uf4
> SPEC ww1_s1uf2 (Left (Left (Left (SR s2_alTo
> 
> ___
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/glasgow-haskell-users


join points and stream fusion?

2017-04-27 Thread Christian Höner zu Siederdissen
Dear all,

have some of you experienced bad code generation in ghc-8.2-rc1 in
combination with stream fusion from the vector package?

Unfortunately, the problem occurs with ADPfusion code which means no
simple example, but I'm asking because of the following core below.

In ghc-8.0 I have nice core, here however constructor specialization has
not happened, neither with the Left/Right nor with the SPEC.

The running time in ghc-8.0 is 2.6 seconds, in rc-1 10.9 seconds.

Best,
Christian

joinrec {
  $wfoldlM'_loop2_s1uf4
  $wfoldlM'_loop2_s1uf4 w_s1ueX ww1_s1uf2 w1_s1ueZ
= case w_s1ueX of { __DEFAULT ->
  case w1_s1ueZ of {
Left sa_au90 ->
  case sa_au90 of {
Left sa1_XuNq ->
  case sa1_XuNq of {
Left sa2_XuNe ->
  case sa2_XuNe of {
SL s2_alTo k_alTp ->
  case k_alTp of {
__DEFAULT ->
  jump $wfoldlM'_loop2_s1uf4
SPEC ww1_s1uf2 lvl211_s1IDG;
1# ->
  jump $wfoldlM'_loop2_s1uf4
SPEC ww1_s1uf2 (Left (Left (Left (SR s2_alTo

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


Re: stream fusion, concatMap, exisential seed unboxing

2015-02-02 Thread Christian Höner zu Siederdissen
Sure, no problem!

Btw. this is not a 'bug' in the usual sense. It is the (neverending)
concatMap + stream fusion story.
https://ghc.haskell.org/trac/ghc/ticket/915
I'm playing a bit with trying to get GHC to look through the existential
seed elements and have it constructor-specialize them.

Unfortunately, unbox/spec fails with more complex seeds for now. For the more
simple cases like the one below, the extra strictness pass works (cool,
thanks!). These are sometimes enough if you have just
concatMap (\i - [i .. j]) stuff.

However, if the internal stream state is, say, a pair (i,j), then one of
those is not completely unboxed. I guess that *if* we could get the
passes to continue unbox'ing and ctor-spec'ing, we could end up with a
fully fused concatMap.

I'll put a complete git repository with criterion + quickcheck modules
up (soonishly ;-).

Viele Gruesse,
Christian

* Simon Peyton Jones simo...@microsoft.com [02.02.2015 15:49]:
 I think it'd help you to open a Trac ticket, give a fully-reproducible test 
 case, including instructions for how to reproduce, and say what isn't 
 happening that should happen. 
 
 What's odd is that loop_s29q looks strict in its Int arg, yet isn't unboxed.  
 There is a way to get the strictness analysis to run twice -flate-dmd-anal.  
 You could try that.
 
 Simon
 
 |  -Original Message-
 |  From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
 |  boun...@haskell.org] On Behalf Of Christian Höner zu Siederdissen
 |  Sent: 01 February 2015 12:18
 |  To: Glasgow-Haskell-Users
 |  Subject: stream fusion, concatMap, exisential seed unboxing
 |  
 |  Hi everybody,
 |  
 |  I'm playing around with concatMap in stream fusion (the vector package
 |  to be exact).
 |  
 |  concatMapM :: Monad m = (a-m (Stream m b)) - Stream m a - Stream m
 |  b concatMapM f (Stream ...) = ...
 |  
 |  I can get my concatMap to behave nicely and erase all Stream and Step
 |  constructors but due to the existential nature of the Stream seeds,
 |  they are re-boxed for the inner stream (which is kind-of annoying
 |  given that the seed is immediately unboxed again ;-). seq doesn't help
 |  here.
 |  
 |  Otherwise, fusion happens for streams and vectors, so that is ok. But
 |  boxing kills performance, criterion says.
 |  
 |  Do we have s.th. in place that could help here? Currently I could use
 |  the vector-concatMap which creates intermediate arrays, my version
 |  which has boxed seeds, or hermit but that is too inconvenient for non-
 |  ghc savy users.
 |  
 |  Viele Gruesse,
 |  Christian
 |  
 |  
 |  
 |  Fusing concatMapM:
 |  
 |  concatMapM f (SM.Stream ostep t _) = SM.Stream step (Left t) Unknown
 |where step (Left t) = do r - ostep t
 | case r of
 |  SM.Done   - return $ SM.Done
 |  SM.Skipt' - return $ SM.Skip (Left
 |  t')
 |  SM.Yield a t' - do s - f a
 |  return $ SM.Skip
 |  (Right (s,t'))
 |  step (Right (SM.Stream istep s _,t)) = do r - istep s
 |case r of
 |  SM.Done   -
 |  return $ SM.Skip(Left t)
 |  SM.Skips' -
 |  return $ SM.Skip(Right (SM.Stream istep s' Unknown,t))
 |  SM.Yield x s' -
 |  return $ SM.Yield x (Right (SM.Stream istep s' Unknown,t))
 |  {-# INLINE [0] step #-}
 |  {-# INLINE [1] concatMapM #-}
 |  
 |  testConcatMapM :: Int - Int
 |  testConcatMapM k = seq k $ U.unId
 |   . SM.foldl' (+) 0
 |   . concatMap (\i - SM.enumFromTo 5 k)
 |   $ SM.enumFromTo 3 k
 |  {-# NOINLINE testConcatMapM #-}
 |  
 |  CORE:
 |  
 |  testConcatMapM
 |  testConcatMapM =
 |\ k_aCA -
 |  let! { I# ipv_s1xv ~ _ - k_aCA } in ### inner loop
 |  letrec {
 |$s$wfoldlM'_loop_s29q
 |$s$wfoldlM'_loop_s29q =
 |  \ sc_s29i sc1_s29j sc2_s29k -
 |  ### unboxing
 |let! { I# x_a1LA ~ _ - sc1_s29j } in
 |case tagToEnum# (=# x_a1LA ipv_s1xv) of _ {
 |  False - $s$wfoldlM'_loop1_s29c sc_s29i sc2_s29k;
 |  True -
 |$s$wfoldlM'_loop_s29q
 |  ### reboxing
 |  (+# sc_s29i x_a1LA) (I# (+# x_a1LA 1)) sc2_s29k
 |};
 |  ### outer loop
 |$s$wfoldlM'_loop1_s29c
 |$s$wfoldlM'_loop1_s29c =
 |  \ sc_s29a sc1_s29b -
 |case tagToEnum# (=# sc1_s29b ipv_s1xv) of _ {
 |  False - sc_s29a;
 |  True -
 |case tagToEnum# (=# 5 ipv_s1xv) of _ {
 |  False - $s$wfoldlM'_loop1_s29c sc_s29a (+# sc1_s29b
 |  1); ### boxed seed (I# 6)
 |  True - $s$wfoldlM'_loop_s29q (+# sc_s29a 5) (I# 6)
 |  (+# sc1_s29b 1

Re: stream fusion, concatMap, exisential seed unboxing

2015-02-02 Thread Christian Höner zu Siederdissen
Yes,

I'm kinda hoping that fusion-interested folks might have a comment.

Both QuickCheck and Criterion are completely optional. It depends only
on base and vector. I'm keeping vector for now, as this allows me to
observe if intermediate vectors are fused away, too.

Viele Gruesse,
Christian

* Simon Peyton Jones simo...@microsoft.com [02.02.2015 18:09]:
 Ah, well, if it's really the concat/concatMap problem then I'm really not 
 sure how to crack it.  
 
 But there are lots of smart people on this list, so maybe someone else can.
 
 The fewer dependencies your test case has the better.  eg Don't use 
 criterion; this stuff is huge: you get 10G of allocation in your test run 
 instead of 10M.   Or something.
 
 Simon
 
 |  -Original Message-
 |  From: Christian Höner zu Siederdissen
 |  [mailto:choe...@tbi.univie.ac.at]
 |  Sent: 02 February 2015 16:02
 |  To: Simon Peyton Jones
 |  Cc: Glasgow-Haskell-Users
 |  Subject: Re: stream fusion, concatMap, exisential seed unboxing
 |  
 |  Sure, no problem!
 |  
 |  Btw. this is not a 'bug' in the usual sense. It is the (neverending)
 |  concatMap + stream fusion story.
 |  https://ghc.haskell.org/trac/ghc/ticket/915
 |  I'm playing a bit with trying to get GHC to look through the
 |  existential seed elements and have it constructor-specialize them.
 |  
 |  Unfortunately, unbox/spec fails with more complex seeds for now. For
 |  the more simple cases like the one below, the extra strictness pass
 |  works (cool, thanks!). These are sometimes enough if you have just
 |  concatMap (\i - [i .. j]) stuff.
 |  
 |  However, if the internal stream state is, say, a pair (i,j), then one
 |  of those is not completely unboxed. I guess that *if* we could get the
 |  passes to continue unbox'ing and ctor-spec'ing, we could end up with a
 |  fully fused concatMap.
 |  
 |  I'll put a complete git repository with criterion + quickcheck modules
 |  up (soonishly ;-).
 |  
 |  Viele Gruesse,
 |  Christian
 |  
 |  * Simon Peyton Jones simo...@microsoft.com [02.02.2015 15:49]:
 |   I think it'd help you to open a Trac ticket, give a fully-
 |  reproducible test case, including instructions for how to reproduce,
 |  and say what isn't happening that should happen.
 |  
 |   What's odd is that loop_s29q looks strict in its Int arg, yet isn't
 |  unboxed.  There is a way to get the strictness analysis to run twice -
 |  flate-dmd-anal.  You could try that.
 |  
 |   Simon
 |  
 |   |  -Original Message-
 |   |  From: Glasgow-haskell-users [mailto:glasgow-haskell-users-
 |   | boun...@haskell.org] On Behalf Of Christian Höner zu Siederdissen
 |   |  Sent: 01 February 2015 12:18
 |   |  To: Glasgow-Haskell-Users
 |   |  Subject: stream fusion, concatMap, exisential seed unboxing
 |   |
 |   |  Hi everybody,
 |   |
 |   |  I'm playing around with concatMap in stream fusion (the vector
 |   | package  to be exact).
 |   |
 |   |  concatMapM :: Monad m = (a-m (Stream m b)) - Stream m a -
 |   | Stream m  b concatMapM f (Stream ...) = ...
 |   |
 |   |  I can get my concatMap to behave nicely and erase all Stream and
 |   | Step  constructors but due to the existential nature of the Stream
 |   | seeds,  they are re-boxed for the inner stream (which is kind-of
 |   | annoying  given that the seed is immediately unboxed again ;-).
 |  seq
 |   | doesn't help  here.
 |   |
 |   |  Otherwise, fusion happens for streams and vectors, so that is ok.
 |   | But  boxing kills performance, criterion says.
 |   |
 |   |  Do we have s.th. in place that could help here? Currently I could
 |   | use  the vector-concatMap which creates intermediate arrays, my
 |   | version  which has boxed seeds, or hermit but that is too
 |   | inconvenient for non-  ghc savy users.
 |   |
 |   |  Viele Gruesse,
 |   |  Christian
 |   |
 |   |
 |   |
 |   |  Fusing concatMapM:
 |   |
 |   |  concatMapM f (SM.Stream ostep t _) = SM.Stream step (Left t)
 |  Unknown
 |   |where step (Left t) = do r - ostep t
 |   | case r of
 |   |  SM.Done   - return $ SM.Done
 |   |  SM.Skipt' - return $ SM.Skip
 |  (Left
 |   |  t')
 |   |  SM.Yield a t' - do s - f a
 |   |  return $ SM.Skip
 |   | (Right (s,t'))
 |   |  step (Right (SM.Stream istep s _,t)) = do r - istep s
 |   |case r of
 |   |  SM.Done
 |  -
 |   |  return $ SM.Skip(Left t)
 |   |  SM.Skips'
 |  -
 |   |  return $ SM.Skip(Right (SM.Stream istep s' Unknown,t))
 |   |  SM.Yield x s'
 |   | -  return $ SM.Yield x (Right (SM.Stream istep s' Unknown,t))
 |   |  {-# INLINE [0] step #-}
 |   |  {-# INLINE [1] concatMapM

stream fusion, concatMap, exisential seed unboxing

2015-02-01 Thread Christian Höner zu Siederdissen
Hi everybody,

I'm playing around with concatMap in stream fusion (the vector package
to be exact).

concatMapM :: Monad m = (a-m (Stream m b)) - Stream m a - Stream m b
concatMapM f (Stream ...) = ...

I can get my concatMap to behave nicely and erase all Stream and Step
constructors but due to the existential nature of the Stream seeds, they
are re-boxed for the inner stream (which is kind-of annoying given that
the seed is immediately unboxed again ;-). seq doesn't help here.

Otherwise, fusion happens for streams and vectors, so that is ok. But boxing
kills performance, criterion says.

Do we have s.th. in place that could help here? Currently I could use the
vector-concatMap which creates intermediate arrays, my version which has boxed
seeds, or hermit but that is too inconvenient for non-ghc savy users.

Viele Gruesse,
Christian



Fusing concatMapM:

concatMapM f (SM.Stream ostep t _) = SM.Stream step (Left t) Unknown
  where step (Left t) = do r - ostep t
   case r of
SM.Done   - return $ SM.Done
SM.Skipt' - return $ SM.Skip (Left t')
SM.Yield a t' - do s - f a
return $ SM.Skip (Right (s,t'))
step (Right (SM.Stream istep s _,t)) = do r - istep s
  case r of
SM.Done   - return $ 
SM.Skip(Left t)
SM.Skips' - return $ 
SM.Skip(Right (SM.Stream istep s' Unknown,t))
SM.Yield x s' - return $ 
SM.Yield x (Right (SM.Stream istep s' Unknown,t))
{-# INLINE [0] step #-}
{-# INLINE [1] concatMapM #-}

testConcatMapM :: Int - Int
testConcatMapM k = seq k $ U.unId
 . SM.foldl' (+) 0
 . concatMap (\i - SM.enumFromTo 5 k)
 $ SM.enumFromTo 3 k
{-# NOINLINE testConcatMapM #-}

CORE:

testConcatMapM
testConcatMapM =
  \ k_aCA -
let! { I# ipv_s1xv ~ _ - k_aCA } in
### inner loop
letrec {
  $s$wfoldlM'_loop_s29q
  $s$wfoldlM'_loop_s29q =
\ sc_s29i sc1_s29j sc2_s29k -
### unboxing
  let! { I# x_a1LA ~ _ - sc1_s29j } in
  case tagToEnum# (=# x_a1LA ipv_s1xv) of _ {
False - $s$wfoldlM'_loop1_s29c sc_s29i sc2_s29k;
True -
  $s$wfoldlM'_loop_s29q
### reboxing
(+# sc_s29i x_a1LA) (I# (+# x_a1LA 1)) sc2_s29k
  };
### outer loop
  $s$wfoldlM'_loop1_s29c
  $s$wfoldlM'_loop1_s29c =
\ sc_s29a sc1_s29b -
  case tagToEnum# (=# sc1_s29b ipv_s1xv) of _ {
False - sc_s29a;
True -
  case tagToEnum# (=# 5 ipv_s1xv) of _ {
False - $s$wfoldlM'_loop1_s29c sc_s29a (+# sc1_s29b 1);
### boxed seed (I# 6)
True - $s$wfoldlM'_loop_s29q (+# sc_s29a 5) (I# 6) (+# 
sc1_s29b 1)
  }
  }; } in
let! { __DEFAULT ~ ww_s20G - $s$wfoldlM'_loop1_s29c 0 3 } in
I# ww_s20G

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


'import ccall unsafe' and parallelism

2014-08-14 Thread Christian Höner zu Siederdissen
Greetings everybody,

I happen to be a bit confused with regards to unsafe foreign imports and
parallelism.

Assume the following C function:

foreign import ccall unsafe cfun
  cfun :: CInt - IO ()

Now, cfun does some work:

go xs = unsafePerformIO $ do
  forM_ xs $ cfun
  return $ somethingUnhealthy

And I'd like to parallelize this:

parMap rdeepseq go [costly,costly]

However, due to the way ghc handles unsafe imports, namely block
everything else whenever 'cfun' is called, I happen to have only one
active 'go'. Lets assume 'cfun' is cheap and would suffer from 'ccall
safe' more than I'd be willing to pay.

Is there any fix possible?

Viele Gruesse,
Christian

PS: The real problem happens to use a bunch of different judy arrays,
each of which lives in its on thread; 300 judy arrays, 300 threads, each
up to 20 million inserts. But I think the basic problem can be reduced
to how to parallelize 'ccall unsafe's.


pgpl7QPupKvqT.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: 'import ccall unsafe' and parallelism

2014-08-14 Thread Christian Höner zu Siederdissen
Thanks,

I've played around some more and finally more than one capability is
active. And indeed, unsafe calls don't block everything. I /had/
actually read that but when I saw the system spending basically only
100% cpu time, I'd thought to ask.

One problem with this program seems to be that the different tasks are
of vastly different sizes. Inputs range from ~ 7x10^1 to ~ 3x10^7
elements inducing waits with the larger problem sizes.

We'll keep the program single-threaded for now as this also keeps memory
consumption at only 25 gbyte instead of the more impressive 70 gbyte in
multi-threaded mode ;-)

Viele Gruesse,
Christian



pgprwoD_OPbcD.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: 'import ccall unsafe' and parallelism

2014-08-14 Thread Christian Höner zu Siederdissen
That's actually a great idea, especially since the safe variants of the
calls are already in place.

* Carter Schonwald carter.schonw...@gmail.com [14.08.2014 23:10]:
have a smart wrapper around you ffi call, and if when you think the ffi
call will take more than 1 microsecond, ALWAYS use the safe ffi call,
i do something like this in an FFI i wrote, it works great
 
On Thu, Aug 14, 2014 at 1:20 PM, Christian HAP:ner zu Siederdissen
choe...@tbi.univie.ac.at wrote:
 
  Thanks,
 
  I've played around some more and finally more than one capability is
  active. And indeed, unsafe calls don't block everything. I /had/
  actually read that but when I saw the system spending basically only
  100% cpu time, I'd thought to ask.
 
  One problem with this program seems to be that the different tasks are
  of vastly different sizes. Inputs range from ~ 7x10^1 to ~ 3x10^7
  elements inducing waits with the larger problem sizes.
 
  We'll keep the program single-threaded for now as this also keeps memory
  consumption at only 25 gbyte instead of the more impressive 70 gbyte in
  multi-threaded mode ;-)
 
  Viele Gruesse,
  Christian
 
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpdqcfI0RC24.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Looking for list comprehensions use cases

2014-07-23 Thread Christian Höner zu Siederdissen
Hi Janek,

yes to both -- in a way. See Section 5.3 here for lists:
http://dl.acm.org/citation.cfm?id=2543736

For my usual work, I use stream fusion and manually 'flatten' everything
in all of ADPfusion and rather large bunch of other work building on top
of that. ;-)

Giegerich's original ADP is full or list comprehensions -- every single
function uses them, and does not require a lot of additional machinery
to run.
http://bibiserv.techfak.uni-bielefeld.de/adp/

Note that if you want to introduce deep optimizations, it'll be a larger
project. See also Coutts' phd thesis ([2] in our paper), and the
original stream fusion paper [3].

Gruss,
Christian

===

[2] D. Coutts. Stream Fusion: Practical Shortcut Fusion for Coinductive
Sequence Types. PhD thesis, University of Oxford, 2010.
[3] D. Coutts, R. Leshchinskiy, and D. Stewart. Stream fusion: From
lists
to streams to nothing at all. In Proceedings of the 12th ACM SIGPLAN
International Conference on Functional Programming, pages 315–
326, Freiburg, Germany, 2007. ACM.

* Jan Stolarek jan.stola...@p.lodz.pl [23.07.2014 13:57]:
 Haskellers,
 
 recently I've been looking into the possibility of creating some new 
 optimisations for GHC. These 
 would be mostly aimed at list comprehensions. Here's where I need your help:
 
 1. Do you have complex list comprehensions usage examples from real code? By 
 complex I mean  
 nested list comprehensions, reading from more than one list ([ ...| x - xs, 
 y - ys ... ]) etc.
 
 2. Do you have list comprehensions code that you had to optimize by hand 
 because GHC was unable to 
 make them fast enough?
 
 Janek
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpBhVdzZa8cz.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: vector and GeneralizedNewtypeDeriving

2014-05-15 Thread Christian Höner zu Siederdissen
Greetings,

As an avid user of unboxed vectors (with a dozen libraries using them
with many newtypes), I've basically been using vector-th-unbox, which is
fine for parameter-free newtypes.

Viele Gruesse,
Christian

* Carter Schonwald carter.schonw...@gmail.com [15.05.2014 04:15]:
this is an issue i'll be running into shortly, otoh I don't think many
folks are writing new unboxed vector instances and related engineering
:)A 
 
On Wed, May 14, 2014 at 10:02 PM, John Lato jwl...@gmail.com wrote:
 
  Hi Richard,
  Thanks for pointing me to the ticket; I agree that's the issue (although
  I'm glad to have you and Simon confirm it). A I've summarized the issue
  and raised the priority, and Simon linked to this thread.
  I would have expected this would have affected a lot users, but as I
  haven't heard many complaints (and nobody else said anything here!)
  maybe the impact is smaller than I thought.
  Thanks,
  John
 
  On Wed, May 14, 2014 at 6:02 AM, Richard Eisenberg e...@cis.upenn.edu
  wrote:
 
Is this an instance ofA https://ghc.haskell.org/trac/ghc/ticket/8177 ?
I think so.
The problem boils down to the fact that Vector and MVector are data
families and are thus (currently) exempted from the roles mechanism.
(Or, more properly, may *only* have nominal roles.) There is no
technical reason for this restriction. It's just that the feature
would take a few solid days of work to implement and I wasn't aware of
a concrete use case.
Here is such a use case.
If you agree that you've hit #8177, please post to that bug report and
raise the priority to High -- being able to coerce Vectors seems very
reasonable indeed, and we should support it. I doubt the feature will
land in 7.8.3 (depending on the timeline for that release), but I'll
get to it eventually. (Or, if you feel this is more critical in the
larger picture, shout more loudly on the ticket and perhaps I can
squeeze it in before 7.8.3.)
Thanks,
Richard
On May 13, 2014, at 9:39 PM, John Lato jwl...@gmail.com wrote:
 
  Hello,
  Prior to ghc-7.8, it was possible to do this:
   module M where
  
   import qualifiedA Data.Vector.Generic.Base as G
   import qualified Data.Vector.Generic.Mutable as M
   import Data.Vector.Unboxed.Base -- provides MVector and Vector
  
   newtype Foo = Foo Int deriving (Eq, Show, Num,
   A  A A M.MVector MVector, G.Vector Vector, Unbox)
  M.MVector is defined as
   class MVector v a where
   A  A  basicLength :: v s a - Int
  etc.
  With ghc-7.8 this no longer compiles due to an unsafe coercion, as
  MVector s Foo and MVector s Int have different types. A The error
  suggests trying -XStandaloneDeriving to manually specify the
  context, however I don't see any way that will help in this case.
  For that matter, I don't see any way to fix this in the vector
  package either. A We might think to define
   type role M.MVector nominal representational
  but that doesn't work as both parameters to M.MVector require a
  nominal role (and it's probably not what we really want anyway).
  A Furthermore Data.Vector.Unboxed.Base.MVector (which fills in at
  `v` in the instance) is a data family, so we're stuck at that point
  also.
  So given this situation, is there any way to automatically derive
  Vector instances from newtypes?
  tl;dr: I would really like to be able to do:
   coerce (someVector :: Vector Foo) :: Vector Int
  am I correct that the current machinery isn't up to handling this?
  Thanks,
  John
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

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



pgpHViYUjKRAe.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: splicing varPs in quasi-quote brackets

2014-03-15 Thread Christian Höner zu Siederdissen
Thanks Adam,

It indeed does work with a lambda, should've thought about it. So, it
seems splices in patterns are new in 7.8 (hadn't seen it in the notes).

Gruss,
Christian

* adam vogt vogt.a...@gmail.com [15.03.2014 05:12]:
 Hello Christian,
 
 It seems new to me that $( ) is allowed in patterns. I would have used
 lamE in something like:
 
 [| $(varE v) = return . SM.concatMapM $(lamE [varP v] (buildRns f
 (xs++[w]) ys))) |]
 
 Regards,
 Adam


pgp_m3hNMryQX.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


splicing varPs in quasi-quote brackets

2014-03-14 Thread Christian Höner zu Siederdissen
Hello everybody,

I wrote me this nice function 'buildRns' which splices in $(varP w) nice
and recursively. Unfortunately, this only seems to work in the 7.8
branch, not in 7.6.3. Is this indeed new, or am I missing something
obvious? The message is:

ADP/Fusion/TH.hs:106:86: Parse error in pattern: $(varP w)

The code works wonderfully in 7.8. It not only compiles, but also
produces working code in applications. I have no problem waiting until
7.8 is stable, but being backwards compatible to 7.6 would be nice.

Many thanks,
Christian

buildRns f xs [] = appE ([| return . SM.singleton |]) 
(foldl (\g z - appE g (varE z)) (return f) xs)
buildRns f xs (VarP v  : ys) = buildRns f (xs++[v]) ys
buildRns f xs (TupP [_,VarP v] : ys) = do w  - newName w
  [| $(varE v) = return . 
SM.concatMapM (\ $(varP w) - $(buildRns f (xs++[w]) ys)) |]
-- 
 ^


pgpcaKR7LsFiI.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: memory ordering

2013-12-20 Thread Christian Höner zu Siederdissen
Hi John,

I guess you probably want to pseq x. See below for an example. Since your 2nd
action does not depend on your 1st.

Gruss,
Christian


import Debug.Trace
import GHC.Conc

main = do
  x - return (traceShow 1 $ 1::Int)
  -- x `pseq` print (2::Int)
  print (2::Int)
  print x


* John Lato jwl...@gmail.com [20.12.2013 02:36]:
Hello,
 
I'm working on a lock-free algorithm that's meant to be used in a
concurrent setting, and I've run into a possible issue.
 
The crux of the matter is that a particular function needs to perform the
following:
 
 x - MVector.read vec ix
 position - readIORef posRef
 
and the algorithm is only safe if these two reads are not reordered (both
the vector and IORef are written to by other threads).
 
My concern is, according to standard Haskell semantics this should be
safe, as IO sequencing should guarantee that the reads happen in-order. 
Of course this also relies upon the architecture's memory model, but x86
also guarantees that reads happen in order.  However doubts remain; I do
not have confidence that the code generator will handle this properly.  In
particular, LLVM may freely re-order loads of NotAtomic and Unordered
values.
 
The one hope I have is that ghc will preserve IO semantics through the
entire pipeline.  This seems like it would be necessary for proper
handling of exceptions, for example.  So, can anyone tell me if my worries
are unfounded, or if there's any way to ensure the behavior I want?  I
could change the readIORef to an atomicModifyIORef, which should issue an
mfence, but that seems a bit heavy-handed as just a read fence would be
sufficient (although even that seems more than necessary).
 
Thanks,
John L.

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



pgpxyOLc1IS90.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GHC 7.8 release?

2013-02-07 Thread Christian Höner zu Siederdissen
Hi Simon,

The download page already has a big Stop there.
http://www.haskell.org/ghc/download_ghc_7_6_2

Apart from that, I am /really/ looking forward to sse/avx extensions and
the official new-code-gen to further narrow the gap between
high-performance C and high-performance Haskell.

That being said, I would be fine using HEAD, but a release is very
convenient in terms of installing, even if they are in the form of rc
(which I typically install to see if something breaks or is faster).

Maybe you want to consider providing a couple of release candidates
instead of 7.8 now?

Gruss,
Christian

* Simon Peyton Jones simo...@microsoft.com [07.02.2013 19:25]:
It's fairly simple in my mind. There are two channels (if I understand
Mark's terminology right):
 
 
 
. Haskell Platform:
 
o   A stable development environment, lots of libraries known to work
 
o   Newcomers, and people who value stability, should use the Haskell
Platform
 
o   HP comes with a particular version of GHC, probably not the hottest
new one, but that doesn't matter.  It works.
 
 
 
. GHC home page downloads:
 
o   More features but not so stable
 
o   Libraries not guaranteed to work
 
o   Worth releasing, though, as a forcing function to fix bugs, and as a
checkpoint for people to test, so that by the time the HP adopts a
particular version it is reasonably solid.
 
 
 
So we already have the two channels Mark asks for, don't we?  One is
called the Haskell Platform and one is called the GHC home page. 
 
That leaves a PR issue: we really don't want newcomers or Joe Users
wanting the new shiny. They want the Haskell Platform, and as Mark says
those users should not pay the slightest attention until it appears in the
Haskell Platform.
 
 
 
So perhaps we principally need a way to point people away from GHC and
towards HP?  eg We could prominently say at every download point Stop! 
Are you sure you want this?  You might be better off with the Haskell
Platform!  Here's why
 
 
 
Have I understood aright?  If so, how could we achieve the right social
dynamics? 
 
 
 
Our goal is to let people who value stability get stability, while the
hot-shots race along in a different channel and pay the price of flat
tires etc.
 
 
 
PS: absolutely right to use 7.6.2 for the next HP.  Don't even think about
7.8.
 
 
 
Simon
 
 
 
 
 
 
 
From: Mark Lentczner [mailto:mark.lentcz...@gmail.com]
Sent: 07 February 2013 17:43
To: Simon Peyton-Jones
Cc: andreas.voel...@gmail.com; Carter Schonwald; GHC users; Simon Marlow;
parallel-haskell; kosti...@gmail.com; Edsko de Vries; ghc-d...@haskell.org
Subject: Re: GHC 7.8 release?
 
 
 
I'd say the window for 7.8 in the platform is about closed. If 7.8 were to
be release in the next two weeks that would be just about the least amount
of time I'd want to see for libraries in the platform to get all stable
with the GHC version. And we'd also be counting on the GHC team to be
quickly responding to bugs so that there could be a point release of 7.8
mid-April. Historically, none of that seems likely.
 
 
 
So my current trajectory is to base HP 2013.2.0.0 on GHC 7.6.2.
 
 
 
Since 7.8 will seems like it will be released before May, we will be faced
again with the bad public relations issue: Everyone will want the new
shiny and be confused as to why the platform is such a laggard. We'll see
four reactions:
 
  o New comers who are starting out and figure they should use the
latest... Many will try to use 7.8, half the libraries on hackage
won't work, things will be wonky, and they'll have a poor experience.
  o People doing production / project work will stay on 7.6 and ignore 7.8
for a few months.
  o The small group of people exploring the frontiers will know how to get
things set up and be happy.
  o Eventually library authors will get around to making sure their stuff
will work with it.
 
I wish GHC would radically change it's release process. Things like 7.8
shouldn't be release as 7.8. That sounds major and stable. The web site
will have 7.8 at the top. The warning to use the platform will fall flat
because it makes the platform look out of date. Really, 7.8 should be in
a different release channel, not on the front page. It should bake in that
channel for six months - where only the third group of people will use it,
until it is getting close to merge into main, at which point the fourth
group will start to use it, so that the day it hits main, all the
libraries just work. Ideally, the first two groups of people will not pay
the slightest attention to it until it is further baked.
 
 
 
While we achievements of the GHC team are great, less than 

Re: Advice on type families and non-injectivity?

2013-01-13 Thread Christian Höner zu Siederdissen
Hi,

How would you infer a from F a? Given bar :: Bool, I can't see how
one could go from Bool to F a = Bool and determine a uniquely.

My question is not completely retorical, if there is an answer I would
like to know it :-)

Gruss,
Christian


* Conal Elliott co...@conal.net [13.01.2013 20:13]:
I sometimes run into trouble with lack of injectivity for type families.
I'm trying to understand what's at the heart of these difficulties and
whether I can avoid them. Also, whether some of the obstacles could be
overcome with simple improvements to GHC.
 
Here's a simple example:
 
 {-# LANGUAGE TypeFamilies #-}

 type family F a

 foo :: F a
 foo = undefined

 bar :: F a
 bar = foo
 
The error message:
 
Couldn't match type `F a' with `F a1'
NB: `F' is a type function, and may not be injective
In the expression: foo
In an equation for `bar': bar = foo
 
A terser (but perhaps subtler) example producing the same error:
 
 baz :: F a
 baz = baz
 
Replacing `a` with a monotype (e.g., `Bool`) eliminates the error.
 
Does the difficulty here have to do with trying to *infer* the type and
then compare with the given one? Or is there an issue even with type
*checking* in such cases?
 
Other insights welcome, as well as suggested work-arounds.
 
I know about (injective) data families but don't want to lose the
convenience of type synonym families.
 
Thanks,  -- Conal

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



pgpDSTt_twtD7.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Advice on type families and non-injectivity?

2013-01-13 Thread Christian Höner zu Siederdissen
Hi Conal,

if you take your example program and write foo :: Bool, ghci accepts it?

For me it complains, and I would think rightly so, that couldn't match
expected type Fa with actual type Bool. It actually only works with the
following quite useless type instance F a = Bool.

By the way, using above instance, the original example works... ;-)

Ultimatively, injective type families would be useful. Thinking about
roman's vector library for example. For my code, I am switching more and
more to data families to get the desired behaviour of: F a ~ F b = a ~ b


Gruss,
Christian

* Conal Elliott co...@conal.net [13.01.2013 21:14]:
Hi Christian,
 
  Given bar :: Bool, I can't see how one could go from Bool to F a =
  Bool and determine a uniquely.
 
The same question applies to foo :: Bool, right? Yet no error message
there.
 
Regards, - Conal
On Sun, Jan 13, 2013 at 11:36 AM, Christian Ho:ner zu Siederdissen
choe...@tbi.univie.ac.at wrote:
 
  Hi,
 
  How would you infer a from F a? Given bar :: Bool, I can't see how
  one could go from Bool to F a = Bool and determine a uniquely.
 
  My question is not completely retorical, if there is an answer I would
  like to know it :-)
 
  Gruss,
  Christian
 
  * Conal Elliott co...@conal.net [13.01.2013 20:13]:
  I sometimes run into trouble with lack of injectivity for type
  families.
  I'm trying to understand what's at the heart of these difficulties
  and
  whether I can avoid them. Also, whether some of the obstacles could
  be
  overcome with simple improvements to GHC.
  
  Here's a simple example:
  
   {-# LANGUAGE TypeFamilies #-}
  
   type family F a
  
   foo :: F a
   foo = undefined
  
   bar :: F a
   bar = foo
  
  The error message:
  
  Couldn't match type `F a' with `F a1'
  NB: `F' is a type function, and may not be injective
  In the expression: foo
  In an equation for `bar': bar = foo
  
  A terser (but perhaps subtler) example producing the same error:
  
   baz :: F a
   baz = baz
  
  Replacing `a` with a monotype (e.g., `Bool`) eliminates the error.
  
  Does the difficulty here have to do with trying to *infer* the type
  and
  then compare with the given one? Or is there an issue even with
  type
  *checking* in such cases?
  
  Other insights welcome, as well as suggested work-arounds.
  
  I know about (injective) data families but don't want to lose the
  convenience of type synonym families.
  
  Thanks,  -- Conal
 
   ___
   Glasgow-haskell-users mailing list
   Glasgow-haskell-users@haskell.org
   http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpQQPvW8QNiU.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] ANNOUNCE: GHC version 7.6.1

2012-09-07 Thread Christian Höner zu Siederdissen
Hi Simon,

Yes I am using -fnew-codegen. Using a large set of random input data
I get the expected results (comparing to both, a different version in
Haskell, and one in C).

I'll be monitoring output and will report problems.

However not relying on it, except to show that high performance is
possible. All code I am using for ``production purposes'' uses GHC 7.4
due to library dependencies.

Thanks for the note!
Christian

* Simon Marlow marlo...@gmail.com [07.09.2012 09:47]:
 On 06/09/2012 21:10, Christian Hoener zu Siederdissen wrote:
 Hi Ian,
 
 thanks for the info about 7.8. Just to be clear, the new codegen
 apparently saved my runtimes for the presentation on tuesday. \My\ new
 code was slower than my old code. The new code generator fixed that,
 giving me equal running times with much cooler features. I currently
 assume (without having checked at all) due to dead variable elimination.
 
 So if it is getting better, I'd be really really happy.
 
 Just to be clear - you're using -fnew-codegen, with GHC 7.6.1?
 
 There were a handful of bugfixes to the new codegen path that didn't
 make it into 7.6.1, so I wouldn't rely on it.
 
 Cheers,
   Simon
 
 
 Gruss,
 Christian
 
 * Ian Lynagh i...@well-typed.com [06.09.2012 22:00]:
 On Thu, Sep 06, 2012 at 06:32:38PM +0200, Christian Hoener zu Siederdissen 
 wrote:
 Awesome,
 
 I have been playing with GHC 7.6.0 until today and been very happy. Btw.
 isn't this the version that officially includes -fnew-codegen / HOOPL?
 
 Because the new codegen is optimizing the my ADPfusion library nicely.
 I lost 50% speed with new features, gained 100% with new codegen,
 meaning new features come for free ;-)
 
 I suspect that you'll find that the new codegen doesn't work 100%
 perfectly in 7.6, although I don't know the details - perhaps it just
 isn't as fast as it could be. It'll be the default in 7.8, though.
 
 
 Thanks
 Ian
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 


pgpFFvD9vRMpE.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC 7.4.2 Release Candidate 1

2012-05-18 Thread Christian Höner zu Siederdissen
Hi,

right now it seems that my ADPfusion stuff works, apparently no bugs.
The runtimes seem to have improved a bit, too. :-) (Could be due to
other changes I currently make due to reviewers' suggestions...)

If anybody has a binary package for ARM in general, I can test that,
too. Unfortunately, I currently don't have the time to build ARM from
source, or try fc18 or Ubuntu for ARM.

I have a trimslice, running Archlinux for ARM.

Gruss,
Christian

* Ian Lynagh ig...@earth.li [16.05.2012 12:07]:
 
 We are pleased to announce the first release candidate for GHC 7.4.2:
 
 http://www.haskell.org/ghc/dist/7.4.2-rc1/
 
 This includes the source tarball, installers for OS X and Windows, and
 bindists for amd64/Linux, i386/Linux, amd64/FreeBSD and i386/FreeBSD.
 
 Please test as much as possible; bugs are much cheaper if we find them
 before the release!
 
 
 Thanks
 Ian, on behalf of the GHC team
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpGJ50kWMAVK.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


optimizer, spec-constr changes 7.2.2 - 7.4

2012-04-30 Thread Christian Höner zu Siederdissen
Hi,

I am currently trying to get my ADPfusion library to optimize code using
ghc-head (same thing described below happens with 7.4.1).

Using ghc-7.2.2, both test programs (Nussinov78 and RNAFold) optimize
well, the performance is close to C and ghc-core shows good code. This
is mostly to say that optimization using ghc-7.2.2 is not an accident
but works reliably.

Unfortunately, with ghc-head it seems that constructor specialization
does not happen. I see a lot of case x of, Left - ..., Right - ...
and case x of, Yield - ... which leads to really bad (slow) code.

As there are some discussions going on regarding the optimizer not
optimizing (like the ticks exhausted [1] one), are there other changes
in the optimizer that could affect it?

spec-constr-count / threshold, simplifier phases, simpl-tick-factor,
no-liberate-case I have tried...

Thanks,
Christian

PS: This is a ask-first-try-to-find-a-simple-example-later mail ;-)


[1] http://hackage.haskell.org/trac/ghc/ticket/5539


pgp7TAx2BsmTr.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


cabal install version selection

2012-03-30 Thread Christian Höner zu Siederdissen
Hi everybody,

I fail to remember or re-google the package version selection for cabal,
if no version constraints are given.

If I depend on iteratee, and there are no constraints, does it take
the lowest version?


When I pushed the newest version of the RNAFold package, the log showed
iteratee-0.1.0 to be used, which failed of course:
http://hackage.haskell.org/packages/archive/RNAFold/1.99.1.0/logs/failure/ghc-7.4

It got really weird, however when I saw that the dependency
BiobaseVienna-0.2.2.3, which is the one actually using iteratee, was
built correctly.

Of course, seeing the error of my way, I have started adding more
version constraints to every package I maintain.



Gruss,
Christian


pgpQSMj7d9gKA.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


ADPfusion: Efficient, high-level dynamic programming

2012-03-24 Thread Christian Höner zu Siederdissen
ADPfusion combines stream-fusion (using the stream interface provided by
the vector library) and type-level programming to provide highly
efficient dynamic programming (DP) combinators.

You can write DP programs in a style similar to Algebraic Dynamic
Programming (ADP) (Giegerich et al.), meaning symbolically without
explicit indices. The symbolic operators provide a number of advantages:

- take care of extracting the correct cell information from data
  structures (DP matrices)
- no more index problems, the grammars are completely free of index
  calculations by the user
- complex operators can be written with next step behaviour dependent
  on other information calculated during runtime
- monadic interface
- works with pure/monadic, boxed/unboxed, ... data structures
- speed close to optimized C (between 1.8x - 3x slower currently --
  compared to well-optimized C-code)

Hackage: http://hackage.haskell.org/package/ADPfusion

1st example program: http://hackage.haskell.org/package/Nussinov78

Many thanks to Roman Leshchinskiy!



Viele Gruesse,
Christian Hoener zu Siederdissen


ADP: http://bibiserv.techfak.uni-bielefeld.de/adp/adpapp.html


pgpoqWAhxsGCv.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: unregisterised and -prof

2012-02-06 Thread Christian Höner zu Siederdissen
It would seem that you are building random with profiling enabled:

4. Build  random-1.0.1.1  by new by  ghc/7.4.1/instUnregis
   by
  ghc --make Setup
  ./Setup configure --prefix=/home/mechvel/ghc/7.4.1/instUnregis/lib/ghc-7.4.1 
-p
  ./Setup build -v

while your non-reg'ged build of ghc has no profiling libraries.
At least that is what this error says:

* Serge D. Mechveliani mech...@botik.ru [06.02.2012 18:20]:
 
 System/Random.hs:97:8:
 Could not find module `Numeric'
 Perhaps you haven't installed the profiling libraries for package `base'?
 Use -v to see a list of the files searched for.
 scico:~/ghc/random/random-1.0.1.1 
 

The easiest is to remove the -p flag, if you do not need profiling enabled.

Gruss,
Christian



pgpoDACqXgpa3.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Unit unboxed tuples

2011-12-23 Thread Christian Höner zu Siederdissen
Hi,

I have to second that. I recently fell over that problem when writing
instances for certain kinds of tuples. In libraries, such as tuple
there is a special 'OneTuple' constructor but I'd really appreciate a
more uniform fix -- but don't know of one either...

Gruss,
Christian

* Ganesh Sittampalam gan...@earth.li [23.12.2011 15:39]:
 On 23/12/2011 13:46, Ian Lynagh wrote:
  On Fri, Dec 23, 2011 at 01:34:49PM +, Simon Peyton-Jones wrote:
 
  Arguments   Boxed  Unboxed
  3   ( , , )(# , , #)
  2   ( , )  (# , #)
  1  
  0   () (# #)
 
  Simple, uniform.
  
  Uniform horizontally, but strange vertically!
 
 It's worth mentioning that if you want to write code that's generic over
 tuples in some way, the absence of a case for singletons is actually a
 bit annoying - you end up adding something like a One constructor to
 paper over the gap. But I can't think of any nice syntax for that case
 either.
 
 Cheers,
 
 Ganesh
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpzcDYozzaqd.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: repa: fromVector

2011-05-20 Thread Christian Höner zu Siederdissen
Hi,

there is a ticket for 'vector' available with what I need:
http://trac.haskell.org/vector/ticket/15

basically, I need a generalised scan that makes available a partially
initialized vector for each new element.

gen_scan :: Vector v a = Int - (v a - a) - v a

Only that 'a' tends to be a 5-tuple ;-)

A function along those lines is extremely useful in a number of cases. I
hope to have some time to actually dig through the repa sources and see
what is possible.

Gruss,
Christian

* Ben Lippmeier b...@ouroborus.net [20.05.2011 04:14]:
 
 On 19/05/2011, at 8:27 PM, Christian Höner zu Siederdissen wrote:
 
  I'd like to use repa in a rather perverted mode, I guess:
  
  for my programs I need to be able to update arrays in place and
  repeatedly perform operations on them.
  Right now, it basically works like this (in ST):
  
  - create unboxed space using primitive (same as unboxed vectors)
  - unsafefreeze unboxed space
  - perform calculations on frozen, immutable space
  - write result into mutable space (which is shared with the unsafefrozen
   space)
 
 If you care deeply about inplace update, then you could use the parallel 
 array filling functions directly. The ones in  D.A.Repa.Internals.Eval*.hs. 
 For 2D images, use the fillVectorBlockwiseP [1] or fillCursoredBlock2P.
 
 
 fillVectorBlockwiseP 
   :: Elt a
   = IOVector a   -- ^ vector to write elements into
   - (Int - a)   -- ^ fn to evaluate an element at the given 
 index
   - Int  -- ^ width of image.
   - IO ()
 
 
 -- | Fill a block in a 2D image, in parallel.
 --   Coordinates given are of the filled edges of the block.
 --   We divide the block into columns, and give one column to each thread.
 fillCursoredBlock2P
   :: Elt a
   = IOVector a   -- ^ vector to write elements into
   - (DIM2   - cursor)   -- ^ make a cursor to a particular 
 element
   - (DIM2   - cursor - cursor) -- ^ shift the cursor by an offset
   - (cursor - a)-- ^ fn to evaluate an element at the 
 given index.
   - Int  -- ^ width of whole image
   - Int  -- ^ x0 lower left corner of block to fill
   - Int  -- ^ y0 (low x and y value)
   - Int  -- ^ x1 upper right corner of block to fill
   - Int  -- ^ y1 (high x and y value, index of last elem 
 to fill)
   - IO ()
 
 
 Actually, it might be worthwhile exporting these in the API anyway.
 
 [1] 
 http://code.ouroborus.net/repa/repa-head/repa/Data/Array/Repa/Internals/EvalBlockwise.hs
 [2] 
 http://code.ouroborus.net/repa/repa-head/repa/Data/Array/Repa/Internals/EvalCursored.hs
 
 


pgpwZSsfvrOv6.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


repa: fromVector

2011-05-19 Thread Christian Höner zu Siederdissen
Hi,

I'd like to use repa in a rather perverted mode, I guess:

for my programs I need to be able to update arrays in place and
repeatedly perform operations on them.
Right now, it basically works like this (in ST):

- create unboxed space using primitive (same as unboxed vectors)
- unsafefreeze unboxed space
- perform calculations on frozen, immutable space
- write result into mutable space (which is shared with the unsafefrozen
  space)

- In principle, this should work with repa as well, I think. The
  question is: does Repa.Internals.Base.fromVector any copying, or
  does it just use the unboxed vector as-is internally?

should I expect any problems? ;-)

Gruss,
Christian


pgp6KOMi3jSnI.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Release/git plans

2011-01-20 Thread Christian Höner zu Siederdissen
This is Haskell. One should abstract away the system used. Call it
vcs-ghc@ and vcs.haskell.org ;-)

Gruss,
Christian

* austin seipp a...@hacks.yi.org [20.01.2011 22:19]:
 Point taken, I personally think it's rather minor although it was
 brought up before like I said, so perhaps others think differently.
 
 Either way, I, for one, welcome our new version control overlord.
 
 On Thu, Jan 20, 2011 at 3:09 PM, Isaac Dupree
 m...@isaac.cedarswampstudios.org wrote:
  On 01/20/11 11:57, austin seipp wrote:
 
  The GHC git repo that
  we'll be using is here:
 
   http://darcs.haskell.org/ghc.git
 
  This is an incredibly minor note in my opinion (that was brought up
  before IIRC) but, isn't it a little strange for ghc's git repository
  to exist on darcs.haskell.org? Not that it's a problem, just slightly
  confusing I guess.
 
  Yes, and the commits mailing-list is still called cvs-...@haskell.org.
   The niceness of sounding right tends to be outweighed by the inconvenience
  of switching :)
 
  -Isaac
 
  ___
  Glasgow-haskell-users mailing list
  Glasgow-haskell-users@haskell.org
  http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
 
 
 
 
 -- 
 Regards,
 Austin
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpncMFW5zZsL.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: lib for tuples

2011-01-04 Thread Christian Höner zu Siederdissen
That would not be economical. Lets just say people never use more than
8-tuple and then try to count how many functions you would need.

The tuple package on Haskell provides a generic interface to
access/manipulate the k'th element of an n-tuple. That should be
sufficient and is not subject to combinatorical explosion (well the
instance are a bit).

Gruss,
Christian

* Serge D. Mechveliani mech...@botik.ru [04.01.2011 11:29]:
 People,
 I define, for example, 
   tuple42(_, y, _, _)   = y,
   setTuple42 (x, _, z, u) y = (x, y, z, u),
   mapTuple42 f (x, y, z, u) = (x, f y, z, u).
 
 But it looks natural to have such functions for tuples in the library.
 As Haskell-2010 has  zip3, zip4 ...,  where are the library functions
 tupleij, setTupleij, mapTupleij,  say, for  i, j - [2 .. 6]
 ?
 I expected to find in the Report Data.Tuple similar as Data.List,
 but do not.
 GHC has Data.Tuple, but it misses the above functions.
 
 Thank you in advance for your comments,
 
 -
 Serge Mechveliani
 mech...@botik.ru
 
 
 
 
 
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpwxCKI5Dnu9.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [Haskell] Terms of Service for Haskell community server

2010-12-15 Thread Christian Höner zu Siederdissen
Hi,

you probably mean generating an ssh key-pair. This is a one-step
operation.

Is Yarrow a weapon or a crypto package?

Otherwise I would suggest putting Yarrow onto your personal webpage /
university system and asking for a link.

Gruss,
Christian

PS: I have just skimmed the TOS, but apart from the crypto (weapon ;-)
stuff, it seems to be mostly standard US legalize. Of course, I am no
lawyer.

* Frank Rosemeier fr...@rosemeier.info [15.12.2010 23:57]:
 
 Dear Haskellers,
 
 as some of you may have noticed, the Yarrow home page has to be
 moved because of the migration of the Haskell.org  server.
 It has been recommended to me by Ian Lynagh to transfer the files to
 the new community server.
 To do so I need first to request for an account there.
 
 This includes producing an ssh certificate. I will try to solve this
 problem. (May be there will be questions in the future.)
 
 The more severe problem is related to the Terms of Service which I
 have to accept with the account request.
 It contains lots of legal stuff which I do not understand including
 regulations for US export controls.
 Of course I am neither able nor willing to send reports concerning
 Yarrow to the US government!
 
 Are there some experts or tutors who want to help me to understand
 the Terms of Service especially the export controls?
 May be these regulations do not apply in my case, because I am
 living in Germany?
 (I have expected lots of work to be done with respect to the migration,
 but I did not imagine to be involved in legal affairs which I do not
 understand.)
 
 Thank you very much for your patience.
 
 
 Kind regards
 
 Frank Rosemeier
 
 ___
 Haskell mailing list
 hask...@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell


pgp5O812UbVFM.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Require OverlappingInstances for the most specific instance only

2010-11-16 Thread Christian Höner zu Siederdissen
The change should not affect working programs, as it just allows you to
define further places where you say that you want an overlapping
instance.

Gruss,
Christian

* Serge D. Mechveliani mech...@botik.ru [16.11.2010 16:47]:
 On Tue, Oct 26, 2010 at 09:41:58PM +0200, John Smith wrote:
  In the case of overlapping instance declarations, GHC currently requires 
  the less specific instance to be compiled with OverlappingInstances for the 
  more specific instance to be usable. This means that, for example, if you 
  write
  
  type ChessBoard = Array (Int,Int) Piece
  
  there is no way to
  
  instance Show ChessBoard where
  show board = ...
  
  because Array is already an instance of Show, and was not compiled with 
  OverlappingInstances.
  
  http://hackage.haskell.org/trac/ghc/ticket/3877 requests that 
  OverlappingInstances be required for only the most specific instance 
  declarations, as suggested in the documentation. Perhaps the rule should 
  instead say that the overlapping instance declaration should be compiled in 
  this way, rather than the overlapped one ... We are interested to receive 
  feedback on these points.
  
  SPJ offered to make this change, if the list users agree. (See comment 6.) 
  Proposed deadline for discussion is 16th November.
 
 
 
 I always expected that such programs as above must be valid. 
 On the other hand, I do not understand these possible ways of compilation, 
 these words about compiled in this way, rather than the overlapped one. 
 Now, as I already have overlapping instances work in my programs, for a 
 long time, it is difficult for me to predict the consequences of the 
 change.
 Can the team issue the corresponding GHC pre-release for testing,
 without making a decision for future before the users report their 
 impression?  
 
 With kind regards, 
 
 -
 Serge Mechveliani
 mech...@botik.ru
  
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgp9H6zJvHSoP.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Loop optimisation with identical counters

2010-11-02 Thread Christian Höner zu Siederdissen
Hi,

is the following problem a job for ghc or the code generation backend
(llvm)?

We are given this program:

{-# LANGUAGE BangPatterns #-}

module Main where

f :: Int - Int - Int - Int - Int
f !i !j !s !m
  | i == 0= s+m
  | otherwise = f (i-1) (j-1) (s + i+1) (m + j*5)

g :: Int - Int
g !k = f k k 0 0


ff :: Int - Int - Int - Int
ff !i !s !m
  | i == 0= s+m
  | otherwise = ff (i-1) (s + i+1) (m + i*5)

gg :: Int - Int
gg !k = ff k 0 0

main = do
  print $ g 20
  print $ gg 20


Here, 'f' and 'g' are a representation of the code I have. Both counters
'i' and 'j' in 'f' count from the same value with the same step size and
terminate at the same time but are not reduced to just one counter. Can
I reasonably expect this to be done by the code generator?
'ff' represents what I would like to see.

Btw. look at the core, to see that indeed 'f' keep four arguments.
Functions like 'f' are a result of vector-fusion at work but can be
written by oneself as well. The point is that if 'f' gets reduced to
'ff' then I can have this:

fun k = zipWith (+) (map f1 $ mkIdxs k) (map f2 $ mkIdxs k)

which makes for nicer code sometimes; but before rewriting I wanted to
ask if that kills performance.


Thanks,
Christian


pgpmeFwIBNFcB.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Proposal: Require OverlappingInstances for the most specific instance only

2010-10-26 Thread Christian Höner zu Siederdissen
Hi,

can't remember to have been hit by it; but changing would mean that
library maintainers can act more conservatively. Otherwise one needs to
be able to guess if an instance might be overlapped.

The new version wouldn't require that, yes?

Gruss,
Christian

* John Smith volderm...@hotmail.com [26.10.2010 21:45]:
 In the case of overlapping instance declarations, GHC currently
 requires the less specific instance to be compiled with
 OverlappingInstances for the more specific instance to be usable.
 This means that, for example, if you write
 
 type ChessBoard = Array (Int,Int) Piece
 
 there is no way to
 
 instance Show ChessBoard where
 show board = ...
 
 because Array is already an instance of Show, and was not compiled with 
 OverlappingInstances.
 
 http://hackage.haskell.org/trac/ghc/ticket/3877 requests that
 OverlappingInstances be required for only the most specific instance
 declarations, as suggested in the documentation. Perhaps the rule
 should instead say that the overlapping instance declaration should
 be compiled in this way, rather than the overlapped one ... We are
 interested to receive feedback on these points.
 
 SPJ offered to make this change, if the list users agree. (See
 comment 6.) Proposed deadline for discussion is 16th November.
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgptcpUG2GJvU.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Cabal constraint solver

2010-10-02 Thread Christian Höner zu Siederdissen
Hi,

does the Cabal constraint solver always try to solve the complete graph?

example: (ghc-7.0.0-rc1)

$ cabal install parsec-3.1.0
cabal: cannot configure syb-0.2.1. It requires base =4.0  4.3

cd syb-0.2.1
* remove base4.3 constraint from syb.cabal
cabal install
* syb-0.2.1 is now installed and works!

$ cabal install parsec-3.1.0
cabal: cannot configure syb-0.2.1. It requires base =4.0  4.3



This is rather annoying: the constraint is solved (eg. syb is installed)
but we /still/ assume that we can not continue. So obviously, I would
like to be able to have cabal assume constraints fullfilled if the
package is installed.

Am I missing something? (Otherwise, testing packages with 7-rc1 is
becoming annoying as almost everything depends on syb)

===

And a second thing: cabal fetch
How does one disable the solver for fetching packages? It is a bit
annoying (here too) that 'cabal fetch parsec-3.1.0' fails. (It should
maybe warn that constraints can not be fulfilled but the idea here is to
get the packages to change them manually)

===

So did I miss anything or can I write a bug report? ;-)



Gruss,
Christian



pgprXMBON3t6B.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Cabal constraint solver

2010-10-02 Thread Christian Höner zu Siederdissen
Hi,

thanks to you all for the answers. I will then go with increasing the
version number for testing, this seems to be the easiest way to go.

And indeed, 'cabal unpack' fetches ( ;-) ) the package without checking
that constraints are met.

Gruss,
Christian

* Christian Höner zu Siederdissen choe...@tbi.univie.ac.at [03.10.2010 00:07]:
 Hi,
 
 does the Cabal constraint solver always try to solve the complete graph?
 
 example: (ghc-7.0.0-rc1)
 
 $ cabal install parsec-3.1.0
 cabal: cannot configure syb-0.2.1. It requires base =4.0  4.3
 
 cd syb-0.2.1
 * remove base4.3 constraint from syb.cabal
 cabal install
 * syb-0.2.1 is now installed and works!
 
 $ cabal install parsec-3.1.0
 cabal: cannot configure syb-0.2.1. It requires base =4.0  4.3
 
 
 
 This is rather annoying: the constraint is solved (eg. syb is installed)
 but we /still/ assume that we can not continue. So obviously, I would
 like to be able to have cabal assume constraints fullfilled if the
 package is installed.
 
 Am I missing something? (Otherwise, testing packages with 7-rc1 is
 becoming annoying as almost everything depends on syb)
 
 ===
 
 And a second thing: cabal fetch
 How does one disable the solver for fetching packages? It is a bit
 annoying (here too) that 'cabal fetch parsec-3.1.0' fails. (It should
 maybe warn that constraints can not be fulfilled but the idea here is to
 get the packages to change them manually)
 
 ===
 
 So did I miss anything or can I write a bug report? ;-)
 
 
 
 Gruss,
 Christian
 



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



pgpdwJveguk35.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHC 6.13 + Data.Vector experiences

2010-09-22 Thread Christian Höner zu Siederdissen
Hi,

I am about to upload a number of packages to hackage. They are all
needed by RNAFoldProgs. The main program therein, RNAFold, replicates
RNAfold of the ViennaRNA package. The difference is that the algorithm
already uses a newer set of parameters; the C functionality will follow
soon from our lab.

But that is not why this message:

RNAFold requires a total of 15 lookup tables (multidimensional arrays),
from 1-d arrays up to a maximum of 6 dimensions. We write into 5
different 2-dimensional tables. 15 different (and rather complex)
functions are involved in filling the tables. Everything is built upon the
Data.Vector package to facilitate fusion to happen (though it boils down
to map+enumFromN most of the time).

Some measurements on an input sequence show the following:

ViennaRNA / C: 1.75s
6.13.20100826 / llvm / O2: 40s
6.13 / llvm O3 / Odph: 17.5s
6.12.3 / c O3 / Odph: 535s (really, nine minutes [1])

Unfortunately, between last and this week, the time went from ~13s to
18s but instead of fiddling around, I thought to release the packages
for anyone interested.

Please take it only as my personal testbed for Data.Vector and head --
though should you want to use the lib for actual rna secondary structure
prediction, that should work, too.

Anyways, there are probably a number of bugs in there, so be warned.

The target is, of course, to have a runtime of 1.74s on my machine :-)



Thanks to don stewart (uvector), roman leshchinskiy (vector) and simon
peyton jones (default method inlining [1])

[1] 6.12.3 shows just how much the working default method inliner
brings. With 6.12, everything goes through dictionaries which is not
cool if you need to do many millions of min/+ operations (We work on a
ring and instanciate very late in the game).


Viele Gruesse,
Christian


PS: Why are my executables with HEAD like 60mbyte in size?!


pgpONLZNwxefz.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Cost Centre MAIN

2010-09-19 Thread Christian Höner zu Siederdissen
You should either try -auto-all while compiling to get cost centres
for every top-level function or insert cost centres by hand with SCC:

http://haskell.cs.yale.edu/ghc/docs/6.12.2/html/users_guide/profiling.html

Otherwise, MAIN is main = ...

Gruss,
Christian


* Stefan Wehr stefan.w...@gmail.com [19.09.2010 14:11]:
 Hi all,
 
 I'm profiling a Haskell program and now getting that the program
 spents 56% of its individual time in the cost centre MAIN (note the
 capital letters).
 
 I searched the documentation for this cost centre, with no success. In
 all profiling results so far, the individual time spent in MAIN was
 always 0%.
 
 Any hints?
 
 -- Stefan
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgp6T8EHf9vtX.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Cost Centre MAIN

2010-09-19 Thread Christian Höner zu Siederdissen
Yeah that was a bit lazy by me (or bull, if you want...;-); looks like you
have runStmLogger on the top-level of your Main module (MAIN) as well.

What functions are defined there? And what vars?

Gruss,
Christian

* Stefan Wehr stefan.w...@gmail.com [19.09.2010 20:28]:
 2010/9/19 Christian Höner zu Siederdissen choe...@tbi.univie.ac.at:
  You should either try -auto-all while compiling to get cost centres
  for every top-level function or insert cost centres by hand with SCC:
 
  http://haskell.cs.yale.edu/ghc/docs/6.12.2/html/users_guide/profiling.html
 
 Well, I did compile with -auto-all and -caf-all
 
  Otherwise, MAIN is main = ...
 
 Really? Here are the first couple of lines of the detailed profiling
 report I get:
 
 COST CENTRE  MODULE
no.entries  %time %alloc   %time %alloc
 
 MAIN MAIN
  1   0  47.50.2   100.0  100.0
  runStmLoggerMobileGateway.Util.Logging
   5223   0   0.00.0 0.00.0
  mainMain
   5166   1   0.00.0 0.60.2
   main   MobileGateway.LubSyncClient
   5167   5   0.00.0 0.60.2
getUrlMobileGateway.Util.Config
   5274   1   0.00.0 0.00.0
 
 Doesn't look like MAIN is the same as main = 
 
 -- Stefan


pgpLsMakwJpQb.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


haddock and associated data families

2010-09-08 Thread Christian Höner zu Siederdissen
Hi,

haddock seems to produce an error on associated data family decls.:

http://hackage.haskell.org/packages/archive/PrimitiveArray/0.0.2.1/logs/failure/ghc-6.12

line 22, where the errors occurs is exactly this one:

class PrimArrayOps a b where
  data PrimArray  a b :: *-- ^ PrimArray data type

I'll fix it by trying other methods to put comments there. Could someone
enter this as a bug, if it is not done yet? (Assuming it is a bug ;-)

Thanks,
Christian


pgpD9QRopBprL.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


late optimization of typeclass callers

2010-08-26 Thread Christian Höner zu Siederdissen
Hi,

I do have the problem that my code is not completely optimized. We begin
with

-- Ring.hs
class Ring a where
  rmult :: a - a - a
  zero :: a

-- PrimitiveArray.hs
class PrimArrayOps a b where
  data PrimArray a b :: *
  unsafeIndex :: PrimArray a b - a - b

-- PAInstances.hs
-- for any 'a' of Data.Primitive.Types by Roman, have unboxed arrays
instance (Prim a) = PrimArrayOps where
  data PrimArray (Int,Int) a = PaIIxI {-# UNPACK #-} !(Int,Int) {-# UNPACK #-} 
!ByteArray
  unsafeIndex (PaIIxI (mI,mJ) arr) (i,j) = {-# CORE IIxIunsafeIndex #-} case 
(i*(mJ+1)+j) of idx - indexByteArray arr idx

-- RNAfoldFunctions.hs
-- VU.Unbox a, because of the vector package
import Data.Vector.Unboxed as VU
class (Ring a, VU.Unbox a, Prim a) = FoldFunctions a where
  opt = VU.foldl' rmult zero $ base turnertables inp table table i j

base trnr inp m m1 i j = VU.zipWith rmult ms m1s where
  cnt  = j-i-2 -- TODO when to stop?
  ms   = VU.map (\ik - m  `unsafeIndex` ik) $ VU.generate cnt (\k - (i,i+k))
  m1s  = VU.map (\kj - m1 `unsafeIndex` kj) $ VU.generate cnt (\k - (k+1+i,j))
{-# INLINE multibranchCloseBase #-}



If I now use this stuff...
-- [1]
instance Ring Int where
  rmult = min
  zero = 1
instance FoldFunctions Int
module MyProgram where
main = do
  let val = opt trnr inp myM myM1 15 78

I get this core [1]. If I do this
-- [2]
instance Ring Int where
  rmult = min
  zero = 1
instance FoldFunctions Int
  opt = VU.foldl' rmult zero $ base turnertables inp table table i j
module MyProgram where
main = do
  let myM = PrimArray of (Int,Int) with Int values
  ...
  let val = opt trnr inp myM myM1 15 78

Is there a way to get the program without an explicit FoldFunctions instance to
specialize to the same Core as the second? The runtime (Criterion was used) is
7.1us (or worse) for [1] and 2.7us for [2]. I could put nice INLINEs everywhere
but they do not help optimizing. These functions run O(n^2) times, with n
between 100 and 1. The core shows that temporary arrays are even created,
filled, and then the fold run over them.

So basically, can I get code running through several class instances to be
optimized at the caller, where all instances are known? Otherwise I could live
with [2], but as the code will almost always be the same for FoldFunctions
instances, it would be really nice to be able to use the defaults that were
defined on (Ring a, VU.Unbox a, Prim a).

Thanks,
Christian


pgp1tcF39x5kr.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHC-HEAD 19.Aug.2010, llvm, threaded [Memory Exhaustion]

2010-08-20 Thread Christian Höner zu Siederdissen
Hi,

using:
http://www.haskell.org/ghc/dist/current/dist/ghc-6.13.20100819-x86_64-unknown-linux.tar.bz2
parallel-3.1.0.0

and the most-common test program ... ever:

module Main where
import Control.Parallel.Strategies

fib :: Int - Int
fib n
  | n  1 = error n  1
  | n == 1= 1
  | n == 2= 1
  | otherwise = fib (n-1) + fib(n-2)

fibs = parMap rdeepseq fib $ [1..100]
main = do
  mapM_ (putStrLn . show) $ zip [1..] fibs


ghc -fllvm -threaded -rtsopts -O2 Prog.hs

./Prog -- runs slowly through 1..100 [OK]
./Prog +RTS -N2 -RTS -- requests all available memory [NOT OK]

ghc -fllvm -threaded -rtsopts Prog.hs

./Prog +RTS -N2 -RTS -- slowly but [OK]



Can anybody confirm this?

Gruss,
Christian



pgpfof6FwbZjY.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Modules and their explicit export lists (are an annoyance)

2010-06-21 Thread Christian Höner zu Siederdissen
Thanks everybody for your thoughts. Based on what I've read this is what
I will do:

- fork a 'foreign' library, if I need to extend it substantially
- export everything explicitly
- or set namespaces like this:
  - Library (with the more stable interface)
  - Library.Internal (which exports everything)

Because of the rather good versioning system of Cabal (like
library=x.y.z) this seems to be the most practical solution for me.

Though it still would be nice if I could inject functions into other
peoples' namespaces -- so to speak ;-)

Gruss,
Christian


* Christian Höner zu Siederdissen choe...@tbi.univie.ac.at [19.06.2010 20:39]:
 Hi everybody,
 
 I'd like some input on other peoples' thoughts on this. Recently, I
 played around with a library that uses an explicit export list. While
 there are reasons for having one:
 
 - efficiencey (inlining in the module)
 - encapsulation
 
 in practice, it seems to me that they are more annoying than useful. For
 once, it would think that ghc should produce efficient good across
 modules with -O / -O2 anyway.
 But the more important thing is, that it makes extending module
 functionality a pain (eg. if a constructor is not exported using (..)).
 
 So, should I really fork a library just to be able to add a function?
 
 
 
 Btw. there are libraries, where an explicit export list is used, that
 export the right amount of information. For example, in 'vector' enough
 is exported to allow you to extend unboxed vectors.



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



pgpQHU69ZqFzB.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Modules and their explicit export lists (are an annoyance)

2010-06-19 Thread Christian Höner zu Siederdissen
Hi everybody,

I'd like some input on other peoples' thoughts on this. Recently, I
played around with a library that uses an explicit export list. While
there are reasons for having one:

- efficiencey (inlining in the module)
- encapsulation

in practice, it seems to me that they are more annoying than useful. For
once, it would think that ghc should produce efficient good across
modules with -O / -O2 anyway.
But the more important thing is, that it makes extending module
functionality a pain (eg. if a constructor is not exported using (..)).

So, should I really fork a library just to be able to add a function?



Btw. there are libraries, where an explicit export list is used, that
export the right amount of information. For example, in 'vector' enough
is exported to allow you to extend unboxed vectors.


pgpeBQeRzGUiQ.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Parallelization of Dynamic Programming Algorithms

2010-05-16 Thread Christian Höner zu Siederdissen
Hi,

continuing the above discussion Parallel Haskell, 2 year project, here
is what i want to do:

- put an (almost) trivial program here that is a dynamic programming
  program but requires no other knowledge (like Bioinformatics or
  whatever). This one is attached.

- write the same program but using one array for each diagonal so that
  it could be parallelized; using the vector package.

- finally, lets see if something like that works in dph.

- hint: we are typically interested in both, a final result and the
  table(s) for backtracking!



+ other topic: publish Haskell libraries for RNA-folding so that there
is a benchmark against a C program, mainly for Roman and the 2-3 other
people out there using Haskell for bioinformatics ;-)

+ other topic: if I start benchmarking in earnest, should I use HEAD
because of the inliner bugs?

Gruss,
Christian


PS:
Dynamic Programming on a very high level, to see what kind of stuff I
would like to be able to do (in parallel ;-)
http://bibiserv.techfak.uni-bielefeld.de/adp/

-- | example Dynamic Programming (DP) program.

module Main where

import Data.Array.IArray
import System.Environment (getArgs)


run n = arr where
  arr :: Array (Int,Int) Int
  arr = array ((1,1),(n,n)) [ ((i,j),f (i,j)) | i - [1..n], j - [1..n]]
  f (i,j)
| i   j = n -- undefined lower triangular part
| i == j = i -- initialize the main diagonal
-- a calculation that does some work
| otherwise = minimum $ n : [ arr ! (i+1,k) + arr ! (k+1,j-1) | k - [i+1..j-2]]


main = do
  (a:_) - getArgs
  let n = read a
  print $ run n ! (1,n)


pgp8gxXWUCqBO.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Parallel Haskell: 2-year project to push real world use

2010-05-04 Thread Christian Höner zu Siederdissen
* Roman Leshchinskiy r...@cse.unsw.edu.au [04.05.2010 10:02]:
 On 04/05/2010, at 11:10, Christian Höner zu Siederdissen wrote:
 
  * Ben Lippmeier b...@ouroborus.net [04.05.2010 02:21]:
  
  You can certainly create an array with these values, but in the provided 
  code it looks like each successive array element has a serial dependency 
  on the previous two elements. How were you expecting it to parallelise?
  
  actually, in reality it is rather more complex, in a 2d-array, each cell
  (i,j) requires a linear number of accesses to previously calculated
  cells that all have indices bounded by the current (i,j).
  
  One of the simplest codes is like this:
  
  forall i in [1..n]
  forall j in [i..n]
  set (i,j) to: minimum of (i,k)+(k,j) (forall k in [i+1..j-1])
 
 Is this related to wavefront algorithms? Although those only access immediate 
 neighbours IIRC.

There is some similarity, but this problem extends to a lot of dynamic
program algorithms that work on matrices.

 
 In any case, vector could well provide an operation like this:
 
 cant_think_of_a_name :: Vector v a = Int - (v a - a) - v a
 
 The function would take the initialised prefix of the vector (starting with 
 empty) and produce the next element. This would require a bit of hackery 
 underneath but the interface would be safe and pure. Would something like 
 this be useful?

This would be very useful in general, as a number of algorithms that now
require lazy arrays or ST/IO could be written with pure code. With the
correct index transformation, it should be possible to have everything
laid out nicely.

 
  Here http://www.tbi.univie.ac.at/newpapers/Abstracts/98-06-009.ps.gz is
  a description of a parallel version of RNAfold.
 
 IIUC, this parallelises processing of each diagonal but computes the 
 diagonals one after another. Could you perhaps store each diagonal as a 
 separate (parallel) array? That would make things much simpler.

That is no problem at all.

 
  I can make my libraries available under GPLv3, they just need a bit of
  love. This gives you a moderately complex algorithm for which there is,
  too, a highly optimized C version (RNAfold -d2, in the vienna rna
  package).
 
 That would be fantastic!
 
 Roman
 
 


Gruss,
Christian


pgpYlSqAujDbf.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Parallel Haskell: 2-year project to push real world use

2010-05-03 Thread Christian Höner zu Siederdissen
Hi,

on that topic, consider this (rather trivial) array:

a = array (1,10) [ (i,f i) | i -[1..10]] where
  f 1 = 1
  f 2 = 1
  f i = a!(i-1) + a!(i-2)

(aah, school ;)

Right now, I am abusing vector in ST by doing this:

a - new
a' - freeze a
forM_ [3..10] $ \i - do
  write a (a'!(i-1) + a!(i-2))

Let's say I wanted to do something like this in dph (or repa), does that
work? We are actually using this for RNA folding algorithms that are at
least O(n^3) time. For some of the more advanced stuff, it would be
really nice if we could just parallelize.

To summarise: I need arrays that allow in-place updates.

Otherwise, most libraries that do heavy stuff (O(n^3) or worse) are
using vector right now. On a single core, it performs really great --
even compared to C-code that has been optimized a lot.

Thanks and Viele Gruesse,
Christian

* Duncan Coutts duncan.cou...@googlemail.com [30.04.2010 17:11]:
 On Fri, 2010-04-30 at 10:25 -0400, Tyson Whitehead wrote:
  On April 30, 2010 06:32:55 Duncan Coutts wrote:
   In the last few years GHC has gained impressive support for parallel
   programming on commodity multi-core systems. In addition to traditional
   threads and shared variables, it supports pure parallelism, software
   transactional memory (STM), and data parallelism. With much of this
   research and development complete, and more on the way, the next stage
   is to get the technology into more widespread use.
  
  Does this mean DPH is ready for abuse?
 
 This project is about pushing the practical use of the parallel
 techniques that are already mature, rather than about pushing research
 projects along further.
 
 So this project is not really about DPH. On the other hand it's possible
 someone might be able to make more immediate use of the dense, regular
 parallel arrays which has been a recent spinoff of the DPH project. They
 have the advantage of being considerably easier to implement, but much
 less expressive than the full sparse, nested parallel arrays.
 
 Duncan
 
 ___
 Glasgow-haskell-users mailing list
 Glasgow-haskell-users@haskell.org
 http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


pgpHVv3Y8QOSQ.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Parallel Haskell: 2-year project to push real world use

2010-05-03 Thread Christian Höner zu Siederdissen
* Ben Lippmeier b...@ouroborus.net [04.05.2010 02:21]:
 
 You can certainly create an array with these values, but in the provided code 
 it looks like each successive array element has a serial dependency on the 
 previous two elements. How were you expecting it to parallelise?

actually, in reality it is rather more complex, in a 2d-array, each cell
(i,j) requires a linear number of accesses to previously calculated
cells that all have indices bounded by the current (i,j).

One of the simplest codes is like this:

forall i in [1..n]
forall j in [i..n]
set (i,j) to: minimum of (i,k)+(k,j) (forall k in [i+1..j-1])

So, either I use destructive updates or need a tricky way to extend the
already computed part of the array with the new part (i,j). The above
code shows only why I need destructive updates. RNA folding is one of
those where it is needed.

I will try to distill the code down to an example that shows a
possibility for parallelization. I would want to use this for future
algorithms where it makes much more sense (O(n^4) or more), but that
still first update an array element, and then access it later.

Here http://www.tbi.univie.ac.at/newpapers/Abstracts/98-06-009.ps.gz is
a description of a parallel version of RNAfold.

 
 Repa arrays don't support visible destructive update. For many algorithms you 
 should't need it, and it causes problems for parallelisation.
 
 I'm actively writing more Repa examples now.  Can you sent me some links 
 explaining the algorithm that you're using, and some example data + output?
 
 Thanks,
 Ben.
 
 
 
 On 04/05/2010, at 9:21 AM, Christian Höner zu Siederdissen wrote:
 
a = array (1,10) [ (i,f i) | i -[1..10]] where
   f 1 = 1
   f 2 = 1
   f i = a!(i-1) + a!(i-2)
  
  (aah, school ;)
  
  Right now, I am abusing vector in ST by doing this:
  
  a - new
  a' - freeze a
  forM_ [3..10] $ \i - do
   write a (a'!(i-1) + a!(i-2))
  
  Let's say I wanted to do something like this in dph (or repa), does that
  work? We are actually using this for RNA folding algorithms that are at
  least O(n^3) time. For some of the more advanced stuff, it would be
  really nice if we could just parallelize.
  
  To summarise: I need arrays that allow in-place updates.
  
  Otherwise, most libraries that do heavy stuff (O(n^3) or worse) are
  using vector right now. On a single core, it performs really great --
  even compared to C-code that has been optimized a lot.
  
  Thanks and Viele Gruesse,
  Christian
 


pgpvp6koeNTyt.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Parallel Haskell: 2-year project to push real world use

2010-05-03 Thread Christian Höner zu Siederdissen
* Roman Leshchinskiy r...@cse.unsw.edu.au [04.05.2010 02:32]:
 On 04/05/2010, at 09:21, Christian Höner zu Siederdissen wrote:
 
  Hi,
  
  on that topic, consider this (rather trivial) array:
  
  a = array (1,10) [ (i,f i) | i -[1..10]] where
   f 1 = 1
   f 2 = 1
   f i = a!(i-1) + a!(i-2)
  
  (aah, school ;)
  
  Right now, I am abusing vector in ST by doing this:
  
  a - new
  a' - freeze a
  forM_ [3..10] $ \i - do
   write a (a'!(i-1) + a!(i-2))
  
  Let's say I wanted to do something like this in dph (or repa), does that
  work? We are actually using this for RNA folding algorithms that are at
  least O(n^3) time. For some of the more advanced stuff, it would be
  really nice if we could just parallelize.
 
 Do you really just need a prefix sum? These are easily parallelisable if the 
 operator is associative. For instance, you could implement the Fibonacci 
 sequence as:
 
 mapP fst $ scanP (\(a,b) _ - (a+b,a)) (1,0) $ replicateP n (0,0)
 
 and DPH would parallelise it. That's how I would write the above with vector 
 as well.

That is, kind of, the fun part: you have

(1) a number of vectors whose values depend on each other (bad!)
(2) in-place update (bad!)
(3) rather trivial calculations for each element (mostly:
sum, minimum, fold, map, backpermute) (good!), we have simple semiring
calculations here

 
  To summarise: I need arrays that allow in-place updates.
 
 In-place updates + parallelism = bad! That's oversimplifying, of course. But 
 the transformations underlying DPH, for instance, simply don't work in the 
 presence of side effects.

The thing is, you can write the algorithm in a way such that each
operation on index k (whatever dimension k has) only requires access
to values =k and those values will never change again. The problem is
that more than one vector is involved making it less fun to write code
like your fibonacci example.

 
  Otherwise, most libraries that do heavy stuff (O(n^3) or worse) are
  using vector right now. On a single core, it performs really great --
  even compared to C-code that has been optimized a lot.
 
 That's great to know! Do you (or anyone else) by any chance have any 
 benchmarks you could share? At the moment, I'm only benchmarking vector with 
 a couple of rather simplistic algorithms which is a bit of a problem.

I can make my libraries available under GPLv3, they just need a bit of
love. This gives you a moderately complex algorithm for which there is,
too, a highly optimized C version (RNAfold -d2, in the vienna rna
package).
I am giving a talk wednesday, after that I'll prepare the libraries for
hackage.



Gruss,
Christian


pgp0ZLbRkPLyX.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Easily generating efficient instances for classes

2010-02-24 Thread Christian Höner zu Siederdissen
Hi,

I am thinking about how to easily generate instances for a class. Each
instance is a tuple with 1 or more elements. In addition there is a
second tuple with the same number of elements but different type. This
means getting longer and longer chains of something like (...,x3*x2,x2,0).

- template haskell?
- CPP and macros?

Consider arrays with fast access like Data.Vector, but with higher
dimensionality. Basically, I want (!) to fuse when used in Data.Vector
code.

A code abstract follows -- I will put this on hackage if there is
insterest. And please comment if you think of something how to improve
here.


Viele Gruesse,
Christian



-- | Primitive multidimensional tables without bounds-checking. Internally, we
-- used unboxed vectors. Construction expects the highest possible index in
-- each dimension, not the length (which is highest index +1). This choice
-- allows for easier construction using bounded types. Consider: fromList True
-- False [] :: PrimTable Bool Bool which creates a 2-element table.

-- | Fast lookup table: `a` encodes the storage index type, while (!) only
-- requires that the index value is (Enum).

data PrimTable a b = PrimTable
  {-# UNPACK #-} !a -- ^ the highest indices (every index starts at 
0 (or 0,0 ...))
  {-# UNPACK #-} !a -- ^ precalculated multiplication values
  {-# UNPACK #-} !(V.Vector b)  -- ^ storage space



-- | mutable fast lookup table

data MPrimTable s a b = MPrimTable
  {-# UNPACK #-} !a
  {-# UNPACK #-} !a
  {-# UNPACK #-} !(V.MVector s b)



class (V.Unbox b) = PrimTableOperations a b e where

  -- | Fast index operation using precomputed multiplication data. Does
  -- bounds-checking only using assert.
  (!) :: PrimTable a b - e - b
  {-# INLINE (!) #-}

  new :: (PrimMonad s) = e - s (MPrimTable (PrimState s) a b)
  {-# INLINE new #-}

  newWith :: (PrimMonad s) = e - b - s (MPrimTable (PrimState s) a b)
  {-# INLINE newWith #-}

  read :: (PrimMonad s) = MPrimTable (PrimState s) a b - e - s b
  {-# INLINE read #-}

  write :: (PrimMonad s) = MPrimTable (PrimState s) a b - e - b - s ()
  {-# INLINE write #-}

  fromList :: e - b - [(e,b)] - PrimTable a b
  fromList dim init xs = runST $ do
mpt - newWith dim init
mapM_ (\(k,v) - write mpt k v) xs
unsafeFreeze mpt
  {-# INLINE fromList #-}






-- | Two-dimensional tables.

instance (Enum e, V.Unbox b) = PrimTableOperations (Int,Int) b (e,e) where

  (PrimTable (z2,z1) (n2,n1) arr) ! (k2,k1) =
arr `V.unsafeIndex` (fromEnum k2 * n2 + fromEnum k1)
  {-# INLINE (!) #-}

  new (z2',z1') = do
let z2 = fromEnum z2' +1
let z1 = fromEnum z1' +1
marr - M.new $ z2 * z1
return $ MPrimTable (z2,z1) (z1,0) marr

  newWith (z2,z1) v = do
mpt - new (z2,z1)
mapM_ (\k - write mpt k v) [(k2,k1) | k2 - [toEnum 0..z2], k1 - [toEnum 
0..z1]]
return mpt

  read (MPrimTable (z2,z1) (n2,_) marr) (k2,k1) =
M.read marr (fromEnum k2 * n2 + fromEnum k1)

  write (MPrimTable (z2,z1) (n2,_) marr) (k2,k1) v =
M.write marr (fromEnum k2 * n2 + fromEnum k1) v



-- example

jarr :: PrimTable (Int,Int) Double
jarr = fromList (2 :: Int,2 :: Int) 0.0 
[((0,0),1.0),((0,1),2.0),((1,0),3.0),((1,1),4.0)]
runj = [jarr ! (k :: (Int,Int)) | k - [(0,0),(0,1),(1,0),(1,1)]]



pgpmQXnina3fi.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Removing/deprecating -fvia-c

2010-02-15 Thread Christian Höner zu Siederdissen
Hi,

the things I am interested in are:

foldU f init .
mapU (\k - array_1 !: (i,k) `combine` array_2 !: (k,j)) $
enumFromToU i j

where (!:) = fancy_index_op

with both `vector` and `uvector` (then D.V.fold etc).

Since ghc 6.12 there has been no significant difference in using either
backend. Then again, more time is spent indexing than optimising the
tight loop.

Viele Gruesse,
Christian Hoener zu Siederdissen

From: Ian Lynagh ig...@earth.li
 
 
 Hi all,
 
 We are planning to remove the -fvia-c way of compiling code
 (unregisterised compilers will continue to compile via C only, but
 registerised compilers will only use the native code generator).
 We'll probably deprecate -fvia-c in the 6.14 branch, and remove it in
 6.16.
 
 Simon Marlow has recently fixed FP performance for modern x86 chips in
 the native code generator in the HEAD. That was the last reason we know
 of to prefer via-C to the native code generators. But before we start
 the removal process, does anyone know of any other problems with the
 native code generators that need to be fixed first?
 
 
 Thanks
 Ian
 
 


pgpUTSikzBK8H.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Text.Regex.Posix with [String] Result broken?

2010-02-08 Thread Christian Höner zu Siederdissen
Hi,

are Regex'es broken or is this local to my installation? I want to blame 
someone else, see:
http://book.realworldhaskell.org/read/efficient-file-processing-regular-expressions-and-file-name-matching.html
where all result types of [a] are broken, too.

Thanks,
Christian



What to test for:

Prelude :m Text.Regex.Posix
Prelude Text.Regex.Posix aab =~ a :: String
a
Prelude Text.Regex.Posix aab =~ a :: [String]

interactive:1:0:
No instance for (RegexContext Regex [Char] [String])
  arising from a use of `=~' at interactive:1:0-11
Possible fix:
  add an instance declaration for
  (RegexContext Regex [Char] [String])
In the expression: aab =~ a :: [String]
In the definition of `it': it = aab =~ a :: [String]



pgpO5vJH2KoNk.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Control.Parallel.Strategies.parMap CPU usage

2009-03-30 Thread Christian Höner zu Siederdissen
Hi,

thank you very much Simon  Don, for the answers.

The latest head gives great results on parallel programs. All cores are
now always at work as I hoped for. So, too, thanks to everybody involved
in the multicore improvements -- they should come very handy. :-)


Thanks again,
Christian


* Don Stewart d...@galois.com [30.03.2009 19:02]:
 choener:
  Hi,
 
  having tried the 6.10.2rc1 release candidate, I still find that parMap 
  rnf xs on a list of thunks xs does not optimally use all available 
  processors. With N the number of cores, I still see that each block of N 
  thunks (say: x_1 and x_2) has to be calculated before (x3 and x4) will be 
  started.
 
  Would there be hope that compiling the latest head instead of 2009/03/14 
  (rc1) gives better results?
 
 
 Yes, definitely. The HEAD implements all the `par` improvements
 described in the recent multicore runtime paper, as well as giving 
 detailed runtime statistics on spark use.


pgpx9PEE8vxYT.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


X11-1.4.2 on 64bit Fedora 8 fails to build

2008-07-01 Thread Christian Höner zu Siederdissen
Hi,
  
I'm trying to get X11-1.4.1 compiled on a 64 bit x86 Fedora 8 system.
  
runhaskell Setup.hs configure --prefix $HOME/ghc
  
has no problems but

runhaskell Setup.hs build

produces:
  
Preprocessing library X11-1.4.2...
/usr/bin/ld: skipping incompatible /usr/lib/libXinerama.so when
searching for -lXinerama
/usr/bin/ld: cannot find -lXinerama
collect2: ld returned 1 exit status
linking dist/build/Graphics/X11/Types_hsc_make.o failed
command was: /scr/airline/choener/ghc-6.8.3/bin/ghc -optl-lXinerama
\ -optl-lXext -optl-lX11 -optl-L/usr/lib64
\ dist/build/Graphics/X11/Types_hsc_make.o -o
\ dist/build/Graphics/X11/Types_hsc_make


Trying something like

runhaskell Setup.hs configure --ld-options=-nostdlib -L/usr/lib64
runhaskell Setup.hs build --ld-options=-nostdlib -L/usr/lib64

does not change the fact that ld looks in the wrong place for
libXinerama. It looks in /usr/lib, but should look in /usr/lib64.

Btw. I don't have root on the machine.

Thanks,
Christian
Höner zu Siederdissen



pgpBEO4ihqZJE.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHC 6.8.2 and large source files

2008-06-01 Thread Christian Höner zu Siederdissen
Dear Haskell users,

we have an automated system that generates executable haskell source
files. These files have a line count from 1,000 lines up to 28,000
lines. There is only 1 type definition and 5 functions in total in the
file.

We now can compile into executable code some of these programs but the
compiler requires an incredible amount of memory: the 15,000 line
programs easily require 2 GByte of RAM and then the compiler dies.

Are there hints on how to compile large source files? Would it help, for
example to compile each function on its own?

On the following webpage you can find a handcrafted program, albeit with
very few lines, that shows how one of our source files would look like:
http://bibiserv.techfak.uni-bielefeld.de/cgi-bin/adp_MatrixMult

We automatically generate type, algebras and the grammar for our
application.

Thanks,
Christian Höner zu Siederdissen



pgpe6hiYsjeBE.pgp
Description: PGP signature
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users