Re: [Haskell-cafe] Monadic style with Streams (as in Data.Array.Parallel.Stream)

2010-05-16 Thread Stephen Tetley
Hi Mark

What style of Stream programming do you have in mind? In Haskell
there can be at least four styles of Stream programming depending how
you count:

There is the stream as infinite-list - see Wouter Swierstra's
Data.Stream on Hackage and if you have university affiliation look for
the paper Functional Pearl: Streams and Unique Fixed Points by Ralf
Hinze. I think comonadic stream programming is within this style - if
not that makes five styles...

There's Stream fusion (Duncan Coutts, Roman Leshchinskiy, Don
Stewart) where the stream programming is an implementation technique
for particular data-structures - internally recursion is avoided with
a special unfold to get fusion optimizations.

Then there is the Arrow Stream processor style of writing transducers,
used I think by the Fudgets toolkit - streamproc on Hackage.

Possibly not finally, there is Jeremy Gibbons's 'Streaming
representation-changers' style which has relation to the Stream fusion
style but appears to have different aims - see Arithmetic coding with
folds and unfolds with Richard Bird.


None of them are monadic I'm afraid. The Arithmetic coding... paper
might be relevant if you are working with Huffman coding.

http://www.cse.unsw.edu.au/~dons/papers/stream-fusion.pdf
http://www.comlab.ox.ac.uk/jeremy.gibbons/publications/

Best wishes

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


Re: [Haskell-cafe] GADTs and Scrap your Boilerplate

2010-05-16 Thread José Pedro Magalhães
Hi Oscar,

On Sat, May 15, 2010 at 22:19, Oscar Finnsson oscar.finns...@gmail.comwrote:


 (...)

 I guess my questions are:

 1. Is it possible to combine GADTs with Scrap your Boilerplate?


Your GADT encodes an existential datatype. The closest attempt to encode
existential types in (something like) SYB that I know of is in Section 5.3
of Alexey's PhD thesis [1]. Having said that, he uses the spine view, which
makes the generic view in SYB explicit, but this has never been packaged as
a library. So I'm afraid the answer is no. The link above might still be
useful for your understanding of why this is a complex problem, though.


Cheers,
Pedro

[1]
http://igitur-archive.library.uu.nl/dissertations/2009-0518-200422/UUindex.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GADTs and Scrap your Boilerplate

2010-05-16 Thread Ben Millwood
On Sun, May 16, 2010 at 2:34 AM, Tom Hawkins tomahawk...@gmail.com wrote:
 I got the GADT

 data DataBox where
   DataBox :: (Show d, Eq d, Data d) = d - DataBox

 [snip]

 but I can't figure out how to implement gunfold for DataBox.

 The error message is

 Text/XML/Generic.hs:274:23:
     Ambiguous type variable `b' in the constraints:

 I had a similar difficultly in Atom making a GADT a member of Eq.  At
 one point I had my head wrapped around the reason for the problem, but
 now it escapes me.  However, I remember the solution: I created a
 function to convert the GADT into another, unGADT type, which was then
 used to compute (==).
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


Have you tried using StandaloneDeriving (and DeriveDataTypeable)?

According to 
http://www.haskell.org/ghc/docs/6.12.2/html/users_guide/deriving.html#stand-alone-deriving
you can't derive instances for GADTs normally but a standalone
derivation will at least attempt to make an instance as if it was an
ordinary data type.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-16 Thread Andrea Vezzosi
On Thu, May 13, 2010 at 8:13 PM, wren ng thornton w...@freegeek.org wrote:
 Andrea Vezzosi wrote:

 On Thu, May 13, 2010 at 10:51 AM, wren ng thornton w...@freegeek.org
 wrote:

 Andrea Vezzosi wrote:

 wren ng thornton  wrote:

 With this change [1] I can't notice any difference for your
 benchmark[2].
 Then again, all the runTest calls take 0 msec and I've had no luck
 making
 the computation take much time; perhaps your computer can detect a
 difference.

 On my machine, with ghc-6.12.1, yours and the original ErrCPS give
 quite similar results, both ~2x slower than Either.
 However it's important to note that these results are highly dependent
 on the monadic expressions being evaluated, with a different benchmark
 you can get an huge speedup with the CPS versions.

 That's very curious. After installing Criterion, my machine (OSX 10.5.8
 2.8GHz Intel Core2Duo, GHC 6.12.1 with -O2) shows only 1% difference
 between
 my ErrCPS and Either on this benchmark. Alas, I can't print kernel
 density
 graphs since Crieterion charts are broken on 6.12. It seems buggy that
 your
 platform would behave so much differently...

 I got the measurements from the original code, could you share the
 code that uses criterion instead?

 The 1% number was buggy because I hadn't factored the generation of random
 lists out of the benchmark. But, having fixed that, I still can't replicate
 your numbers: I get 12us for Either, vs 17us for EitherCPS.

 http://community.haskell.org/~wren/wren-extras/test/Control/Monad/ErrCPS/CriterionBenchmark.hs



 Yet another version of the same benchmark, this time using Microbench:

 http://community.haskell.org/~wren/wren-extras/test/Control/Monad/ErrCPS/MicrobenchBenchmark.hs

 Microbench seems to replicate your numbers better: 2551.930ns vs 4466.832ns
 (or 391.86 vs 223.87 calls per second)--- though this is getting into the
 range where there might be Int overflow issues corrupting the results (a
 similar problem showed up when benchmarking Data.Trie vs Data.Map), so it
 may warrant further investigation.


That might be the case, i'm on 64bit:

sai...@astarte:~$ uname -a
Linux astarte 2.6.32-ARCH #1 SMP PREEMPT Tue Feb 23 19:43:46 CET 2010
x86_64 Intel(R) Core(TM)2 Duo CPU E8400 @ 3.00GHz GenuineIntel
GNU/Linux

sai...@astarte:~$ ./CriterionBenchmark
warming up
estimating clock resolution...
mean is 6.834442 us (80001 iterations)
found 1240 outliers among 79998 samples (1.6%)
  1131 (1.4%) high severe
estimating cost of a clock call...
mean is 107.2316 ns (41 iterations)

benchmarking Either
collecting 100 samples, 1039 iterations each, in estimated 683.8220 ms
bootstrapping with 10 resamples
mean: 6.563462 us, lb 6.553649 us, ub 6.570454 us, ci 0.950
std dev: 41.74602 ns, lb 23.76971 ns, ub 67.67842 ns, ci 0.950
found 8 outliers among 100 samples (8.0%)
  2 (2.0%) low severe
  4 (4.0%) high mild
  2 (2.0%) high severe
variance introduced by outliers: 0.990%
variance is unaffected by outliers

benchmarking ErrCPS
collecting 100 samples, 1 iterations each, in estimated 1.334000 s
bootstrapping with 10 resamples
mean: 13.14468 ms, lb 13.10442 ms, ub 13.18208 ms, ci 0.950
std dev: 198.3150 us, lb 182.0600 us, ub 220.7957 us, ci 0.950
variance introduced by outliers: 0.993%
variance is unaffected by outliers

If i'm reading it correctly this gives even worse results: 6us vs. 13ms

 --
 Live well,
 ~wren
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

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


Re: [Haskell-cafe] Speed of Error handling with Continuations vs. Eithers

2010-05-16 Thread roconnor

On Fri, 14 May 2010, Derek Elkins wrote:


You did it wrong.  All you did was Church encode the Either type.
Your bind is still doing a case-analysis.  All you have to do is use
ContT r (Either e).  The bind implementation for ContT is completely
independent of the underlying monad.  It doesn't even require the m in
ContT r m to be a functor, let alone a monad.  Therefore the ContT
bind doesn't do any case-analysis because it doesn't know anything
about the underlying monad.  One way to look at what is happening is
to compare it to Andrzej Filiniski's work in Representing Monads and
Representing Layered Monads.


What I don't get is that the bind operation for ContT and ErrCPS look so 
similar to me


ContT (stripping off the newtype constructor/destructors):
m = k  = \c - m (\a - k a c)

ErrCPS (stripping off the newtype constructor/destructors):
m = f = \err good - m err (\x - f x err good)

I don't get why one is slow but not the other?

--
Russell O'Connor  http://r6.ca/
``All talk about `theft,''' the general counsel of the American Graphophone
Company wrote, ``is the merest claptrap, for there exists no property in
ideas musical, literary or artistic, except as defined by statute.''
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Numerical Analysis

2010-05-16 Thread Roman Leshchinskiy
On 16/05/2010, at 10:17, Pierre-Etienne Meunier wrote:

 I've also just noticed a lack in the vector library : multidimensional arrays 
 seem to require indirections like in caml, whereas in C or in Data.Ix, there 
 is a way to avoid this. This is especially important for avoiding cache 
 misses with many dimensions, as well as for providing a clean interface. For 
 instance if a 10x10 matrix is initialized unproperly like 
 
 Data.Vector.replicate 10 $ Data.Vector.replicate 10 0
 
 The result is a total mess. Surely, every programmer knows that a computer 
 has got memory, and that this memory has to be allocated, but from what I 
 understand of haskell, I would expect the interface and the RTS to do it for 
 me. And an integer multiplication, followed by an addition, is way cheaper 
 than accessing uncached memory. Or maybe I do not understand that pipelines, 
 hyperthreading and all that stuff would give you the same result ?

You are quite right that vector only supports nested arrays but not 
multidimensional ones. This is by design, however - the library's only goal is 
to provide efficient one-dimensional, Int-indexed arrays. I'm thinking about 
how to implement multidimensional arrays on top of vector but it's not that 
easy. While repa is a step in that direction, I also need to support mutable 
arrays and interoperability with C which complicates things immensely.

That said, if all you need is a matrix it's quite easy to implement the 
necessary index calculations yourself. Also, since you are working with 
numerics I highly recommend that you use either Data.Vector.Unboxed or 
Data.Vector.Storable instead of Data.Vector as boxing tends to be prohibitively 
expensive in this domain.

Roman


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


Re: [Haskell-cafe] Monadic style with Streams (as in Data.Array.Parallel.Stream)

2010-05-16 Thread Roman Leshchinskiy
On 16/05/2010, at 11:54, Mark Wassell wrote:

 Hi,
 
 This possibly might go against the spirit of what Stream programming is about 
 but I having difficulties converting an imperative algorithm [1] into Haskell 
 and think it would be easier if I was able to write it in a monadic style 
 with operations to read and write from and to the streams.
 
 I first tried to approach it by delving into the innards of other Stream 
 functions to devise what I needed. I only got so far and the sticking point 
 was defining the Monad. I then approached it from the Monad side and although 
 what I have is workable, it probably isn't going to perform (for one it uses 
 fromStream and tailS on each read off the front of the stream).

Data.Array.Parallel.Stream serves only one purpose: to represent loops produced 
by DPH in such a way that the compiler is able to optimise them well. Putting a 
monad on top of that will very very likely break this. To be honest, I'm not 
sure why you need the monad anyway. I would expect compression/decompression to 
be pure functions of type Stream Word8 - Stream Word8.

In any case, I would urgently recommend not to use Data.Array.Parallel.Stream 
for anything at this point. This whole subsystem will soon die of old age and 
be replaced by the much nicer stuff from package vector, specifically 
Data.Vector.Fusion.Stream and Data.Vector.Fusion.Stream.Monadic. Note that the 
latter implements monadic streams as described in 
http://www.cse.unsw.edu.au/~rl/publications/recycling.html. Perhaps those can 
be useful for you if you really need a monad.

Roman


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


[Haskell-cafe] Re: ANN: Monad.Reader Issue 16

2010-05-16 Thread Heinrich Apfelmus
Brent Yorgey wrote:
 I am very pleased to announce that Issue 16 of The Monad.Reader is now
 available [1].
 
 Issue 16 consists of the following three articles:
 
 * Demand More of Your Automata by Aran Donohue
 * Iteratee: Teaching an Old Fold New Tricks by John W. Lato
 * Playing with Priority Queues by Louis Wasserman

Another great issue of my favorite Haskell magazine!


I have a remark on Louis' article. Namely, I think the description of
amortization is a bit unfortunate in a persistent setting like Haskell.
The  inc  example will still take O(1) amortized time, but not because
costs are saved in advance, you can't save anything when things are
persistent. Imagine several clones of you coming from the future and
trying to access your current bank account savings...

The real reason for O(1) is that the changes to the list are lazy and
the cost for the expensive operation is payed as tax by *future*
operations that attempt to extract elements further down the list.
This means that the amortized bound depends on the available functions
for *observing* the data structure, too.

Unfortunately, I think this makes the proof of theorem 27 more subtle:
you need to make sure that you don't pay more than O(log n) in tax for
evaluating the binary number with  log n  digits to normal form! In
other words, each increment might take O(1) time but this could create
so many taxes that printing all digits takes a lot longer.

To demonstrate the issue, consider the function

   bunk :: [Bool] - [Bool]
   bunk (True  : bs) = False : bunk bs
   bunk (False : bs) = True  : bunk bs
   bunk []   = [True]

This will take O(1) time when you only look at the head of the list
afterwards, i.e.

   head . bunk . bunk . ... . bunk $ []

is always O(n). But

   length . bunk . bunk . ... . bunk $ []

will take O(n^2). You'd have to show that this doesn't happen with  inc .


For more on how to do amortized analysis in a persistent setting, see
also Okasaki's book

  Purely Functional Data Structures.
  http://www.cs.cmu.edu/~rwh/theses/okasaki.pdf

I have collected some mailing lists posts on his debit method here:

  http://apfelmus.nfshost.com/articles/debit-method.html


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com

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


[Haskell-cafe] executeFile failing on macosx

2010-05-16 Thread David Powell
executeFile is failing for me on Mac OS X 10.5.8, with ghc 6.12.1 when
compiling with -threaded.  Compiling without -threaded, or running on
linux is fine.

When compiled with -threaded, the following snippet produces the error:
  testProg: /bin/echo: executeFile: failed (Operation not supported)

 import System.Posix.Process
 main = do

  forkProcess $ executeFile /bin/echo False [Ok] Nothing

Any suggestions for a work around for this would be appreciated.

Cheers,

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


Re: [Haskell-cafe] executeFile failing on macosx

2010-05-16 Thread Bulat Ziganshin
Hello David,

Sunday, May 16, 2010, 7:18:29 PM, you wrote:

 executeFile is failing for me on Mac OS X 10.5.8, with ghc 6.12.1
 when compiling with -threaded.  Compiling without -threaded, or running on 
 linux is fine. 
  forkProcess $ executeFile /bin/echo False [Ok] Nothing

afair, forkProcess and -threaded shouldn't work together on any Unix.
can you try forkIO or forkOS instead?



-- 
Best regards,
 Bulatmailto:bulat.zigans...@gmail.com

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


[Haskell-cafe] Getting a string from url-converted UTF8 input

2010-05-16 Thread Eugene Dzhurinsky
Hello all!

Can somebody please explain wha am I doing in wrong way?

===
module UrlEncode where

import System
import Codec.Binary.UTF8.String as SU
import Codec.Binary.Url as U
import Data.Maybe

main :: IO ()
main = do
args - getArgs
processWithArgs args

processWithArgs (-d:[]) =
getLine = putStrLn .  maybe  SU.decode .  U.decode 

processWithArgs (-e:[]) =
getLine = putStrLn . U.encode . SU.encode

processWithArgs _ =
putStrLn Usage: -e (encode) or -d (decode)
===

With this script if fed with input:

===
1%29%20%D0%B3%D0%B4%D0%B5%20%D0%BD%D1%8B%D0%BD%D1%87%D0%B5%20%D0%BC%D0%BE%D0%B4%D0%BD%D0%BE%20%D0%B1%D1%80%D0%B0%D1%82%D1%8C%20%D0%BA%D0%BD%D0%B8%D0%B6%D0%BA%D0%B8%20%D0%B2%20%D0%B2%D0%B8%D0%B4%D0%B5%20FB2%3F%0D%0A%0D%0A2%29%20%D0%BA%D0%B0%D0%BA%D0%BE%D0%B9%20%D0%B5%D1%81%D1%82%D1%8C%20%D1%81%D0%BE%D1%84%D1%82%20%D0%BD%D0%B0%20%D0%B6%D0%B5%D0%BB%D0%B5%D0%B7%D0%BA%D1%83%20%D1%82%D0%B8%D0%BF%D0%B0%20%D1%82%D0%B5%D0%BB%D0%B5%D1%84%D0%BE%D0%BD%20%D1%81%20Symbian
===

I am getting the output:

===
1) 345 =K=G5 4= 1...@0bl :=86:8 2 2845 FB2?

2) :0:9 5ABL ADB =0 65;57:C B8?0 B5;5D= A Symbian
===

which is wrong. So what do I miss in encoding the data in UTF?

Thank you in advance!

-- 
Eugene Dzhurinsky


pgpUPu4ndYSxU.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting a string from url-converted UTF8 input

2010-05-16 Thread Roman Cheplyaka
* Eugene Dzhurinsky b...@redwerk.com [2010-05-16 18:42:08+0300]
 Hello all!
 
 Can somebody please explain wha am I doing in wrong way?
 
 [snip]
 
 I am getting the output:
 
 ===
 1) 345 =K=G5 4= 1...@0bl :=86:8 2 2845 FB2?
 
 2) :0:9 5ABL ADB =0 65;57:C B8?0 B5;5D= A Symbian
 ===
 
 which is wrong. So what do I miss in encoding the data in UTF?

I assume you are using GHC  6.12. The trouble is in conversion done by
putStrLn. Use one from System.IO.UTF8.

Or try to upgrade to GHC 6.12 which respects the locale settings.

-- 
Roman I. Cheplyaka :: http://ro-che.info/
Don't let school get in the way of your education. - Mark Twain
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting a string from url-converted UTF8 input

2010-05-16 Thread Eugene Dzhurinsky
On Sun, May 16, 2010 at 06:56:58PM +0300, Roman Cheplyaka wrote:
 I assume you are using GHC  6.12. The trouble is in conversion done by
 putStrLn. Use one from System.IO.UTF8.
 
 Or try to upgrade to GHC 6.12 which respects the locale settings.

Hello, Roman!

Thank you very much for the hint, it really did help.

Unfortunately, there's no port of GHC 6.12 available for FreeBSD now, so I
used System.IO.UTF8

-- 
Eugene Dzhurinsky


pgp4pa7EBeen7.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Numerical Analysis

2010-05-16 Thread Pierre-Etienne Meunier
 You are quite right that vector only supports nested arrays but not 
 multidimensional ones. This is by design, however - the library's only goal 
 is to provide efficient one-dimensional, Int-indexed arrays. I'm thinking 
 about how to implement multidimensional arrays on top of vector but it's not 
 that easy. While repa is a step in that direction, I also need to support 
 mutable arrays and interoperability with C which complicates things immensely.

I understand. What complicates it even more (at least in what I imagine) is 
that C uses the same syntax for multidimensional and nested arrays, and I do 
not believe that for instance GHC's FFI allows for array types such as int 
x[19][3].

Data.Ix allows for indexing arrays with (Int,Int), for instance, but with 
costly index conversions, constructing lists in the memory for instance. Also, 
sometimes the user of these libraries may find a better bijection between N and 
N^2, better in the sense that for his particular problem, a slightly more 
complicated arithmetic sequence of operations for computing the index would 
optimize cache misses better.

Would it be for instance possible however to generate a default bijection using 
preprocessing (template haskell ?) ?

 That said, if all you need is a matrix it's quite easy to implement the 
 necessary index calculations yourself. Also, since you are working with 
 numerics I highly recommend that you use either Data.Vector.Unboxed or 
 Data.Vector.Storable instead of Data.Vector as boxing tends to be 
 prohibitively expensive in this domain.

I'm actually thinking about rewriting parts of my code now ! It seems indeed 
that given how the algorithms are specified for instance in numerical recipes 
or the papers in its bibliography, unboxing is the only option, since there is 
no such thing as boxing in cobol and fortran ;-)

I was also wondering about how to do linear algebra : an infinite number of 
types would be needed to express all the constraints on matrix multiplication : 
we need types such as array of size m * n. Is there a way to generate these 
automatically with for instance template haskell (again ! But I know nothing of 
template haskell, neither, sorry !)

Cheers,
PE

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


Re: [Haskell-cafe] Getting a string from url-converted UTF8 input

2010-05-16 Thread Daniel Fischer
On Sunday 16 May 2010 18:13:30, Eugene Dzhurinsky wrote:
 On Sun, May 16, 2010 at 06:56:58PM +0300, Roman Cheplyaka wrote:
  I assume you are using GHC  6.12. The trouble is in conversion done
  by putStrLn. Use one from System.IO.UTF8.
 
  Or try to upgrade to GHC 6.12 which respects the locale settings.

 Hello, Roman!

 Thank you very much for the hint, it really did help.

 Unfortunately, there's no port of GHC 6.12 available for FreeBSD now, so
 I used System.IO.UTF8

Is there any problem compiling from source on FreeBSD?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Numerical Analysis

2010-05-16 Thread Gregory Crosswhite

On May 16, 2010, at 4:51 AM, Roman Leshchinskiy wrote:

 You are quite right that vector only supports nested arrays but not 
 multidimensional ones. This is by design, however - the library's only goal 
 is to provide efficient one-dimensional, Int-indexed arrays. I'm thinking 
 about how to implement multidimensional arrays on top of vector but it's not 
 that easy. While repa is a step in that direction, I also need to support 
 mutable arrays and interoperability with C which complicates things immensely.

Indeed;  I eventually decided to hand-roll my own package for dealing with 
N-dimensional arrays using StorableArray under the hood since I needed to be 
able to pass them to and from Fortran routines.  It has some nice features such 
as arbitrary type-safe cuts and slicing (i.e., you can take index 1 of the 
first dimension and every 3rd index between 2 and 9 of the third dimension and 
it will returns a new array with a type that has one fewer dimension), folding, 
converting to/from lists, mutable and immutable versions, and direct pointer 
access --- which is just the amount of functionality I needed for my purposes.  
The problem (and part of the reason I haven't gotten around to uploading it to 
Hackage) is that the package is not geared around performing efficient 
computations in Haskell because I have been writing numeric routines themselves 
in Fortran;  its only real purpose was to let me to examine the arrays in 
Haskell code.

As an aside, while there are advantages to writing numerical analysis routines 
in Haskell, it might be better strategy to instead link in something like 
LAPACK and provide nice wrappers to it in Haskell, since this way you can 
harness the work of the experts who have spent a lot of time perfecting their 
code rather than re-inventing the wheel.  One downside of this, though, is that 
the LAPACK routines only achieve parallelism by making extensive use of Level 3 
BLAS routines whenever possible and assuming that they are heavily optimized 
and parallelized (which they are), so there *might* be cases were a pure 
Haskell implementation might be able to out-perform them by exploiting even 
more opportunities parallelism within the algorithm then that provided by the 
BLAS calls.Another downside is that using LAPACK requires the arrays to be 
in pinned memory --- though only for the duration of the LAPACK call.  Finally, 
I have been experiencing problems linking Fortran and Haskell code on OSX for 
reasons that I don't understand, since I have no problem on my Linux machine, I 
have made sure that all the code is compiled for the 32-bit architecture on my 
OSX machine, and linking C and Fortran programs on the OSX machine does not 
result in any problems.

Cheers,
Greg

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


Re: [Haskell-cafe] [reactive] A pong and integrate

2010-05-16 Thread Limestraël
Eventually, I don't think it is a profiling issue.
Maybe a problem with integral. According to a quite recent post on the
reactive mailing list, the following minimal code produces the same problem
:

 import FRP.Reactive
 import FRP.Reactive.LegacyAdapters

 import Control.Applicative

 type Velocity = Double
 type Position = Double

 data Car = Car { vel :: Velocity, pos :: Position } deriving Show

 velocity :: Behavior Velocity

 velocity = 1

 position :: Behavior Position
 position = integral (atTimes [0, 0.5 ..]) velocity

 car :: Behavior Car
 car = Car $ velocity * position


 main :: IO ()
 main = adaptE $ print $ car `snapshot_` atTimes [0, 0.5..]

 1) why is the leak happen?
 2) how can I fix this problem?

 Some more detailed informations:

 * reactive 0.11.4
 * GHC 6.12.1
 * Gentoo Linux (2.6.32-tuxonice, x86_64) or Ubuntu 9.10 64bits
 * compiled with or without -O2 flag



2010/5/16 David Leimbach leim...@gmail.com



 On Sat, May 15, 2010 at 8:42 AM, Limestraël limestr...@gmail.com wrote:

 Okay,
 guess I'll have to bring out the chapter 25 of my Real World Haskell...


 I find it's often the most practical chapter that I hit a lot during writes
 and changes to my server process I have in Haskell in our control system
 code :-)

 That plus the information that I had missed that Control.Monad.State
 defaulted to the Lazy version (which is consistent, but for some reason it
 got by me) helped me to realize why I was leaking so much space in a garbage
 collected environment.

 I wouldn't have gotten very far with Haskell as this piece of our code
 without that chapter.  I'd love to see more writing of that sort around
 Haskell in book form.  One can become fluent in tuning Haskell by trial and
 error, but the sharp corners one must bump into are often sharper than in
 other languages I've found.

 Dave




 2010/5/15 Bulat Ziganshin bulat.zigans...@gmail.com

 Hello Limestraėl,

 Saturday, May 15, 2010, 7:02:38 PM, you wrote:

  But when I set my beat to tick every 60 times per second, the
  position is well updated, but I clearly see that the display
  dramatically slows down after a few seconds of execution. Too heavy
 rate for integrate?

 it may be due to lot of uncollected garbage that is result of lazy
 evaluation. profile program to check its GC times


 --
 Best regards,
  Bulatmailto:bulat.zigans...@gmail.com



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



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


Re: [Haskell-cafe] [reactive] A pong and integrate

2010-05-16 Thread Peter Verswyvelen
As far as I know, it was never possible to make a pong game in
Reactive, at least not with the versions I tried, but I admit a lot of
never versions got released since then. It would be great to see one
though :)

You might want to try Yampa, that works for sure (although you should
mark all your output data strict, as is done in the examples,
otherwise you might also get space leaks or shaky frame rates). Or
Elerea, which comes with a breakout game.

On Sun, May 16, 2010 at 9:30 PM, Limestraël limestr...@gmail.com wrote:
 Eventually, I don't think it is a profiling issue.
 Maybe a problem with integral. According to a quite recent post on the
 reactive mailing list, the following minimal code produces the same problem
 :

 import FRP.Reactive

 import FRP.Reactive.LegacyAdapters

 import Control.Applicative

 type Velocity = Double
 type Position = Double

 data Car = Car { vel :: Velocity, pos :: Position } deriving Show


 velocity :: Behavior Velocity

 velocity = 1

 position :: Behavior Position
 position = integral (atTimes [0, 0.5 ..]) velocity

 car :: Behavior Car
 car = Car $ velocity * position



 main :: IO ()
 main = adaptE $ print $ car `snapshot_` atTimes [0, 0.5..]

 1) why is the leak happen?
 2) how can I fix this problem?

 Some more detailed informations:


 * reactive 0.11.4
 * GHC 6.12.1
 * Gentoo Linux (2.6.32-tuxonice, x86_64) or Ubuntu 9.10 64bits
 * compiled with or without -O2 flag

 2010/5/16 David Leimbach leim...@gmail.com


 On Sat, May 15, 2010 at 8:42 AM, Limestraël limestr...@gmail.com wrote:

 Okay,
 guess I'll have to bring out the chapter 25 of my Real World Haskell...

 I find it's often the most practical chapter that I hit a lot during
 writes and changes to my server process I have in Haskell in our control
 system code :-)
 That plus the information that I had missed that Control.Monad.State
 defaulted to the Lazy version (which is consistent, but for some reason it
 got by me) helped me to realize why I was leaking so much space in a garbage
 collected environment.
 I wouldn't have gotten very far with Haskell as this piece of our code
 without that chapter.  I'd love to see more writing of that sort around
 Haskell in book form.  One can become fluent in tuning Haskell by trial and
 error, but the sharp corners one must bump into are often sharper than in
 other languages I've found.
 Dave


 2010/5/15 Bulat Ziganshin bulat.zigans...@gmail.com

 Hello Limestraėl,

 Saturday, May 15, 2010, 7:02:38 PM, you wrote:

  But when I set my beat to tick every 60 times per second, the
  position is well updated, but I clearly see that the display
  dramatically slows down after a few seconds of execution. Too heavy
  rate for integrate?

 it may be due to lot of uncollected garbage that is result of lazy
 evaluation. profile program to check its GC times


 --
 Best regards,
  Bulat                            mailto:bulat.zigans...@gmail.com



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




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


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


Re: [Haskell-cafe] Monadic style with Streams (as in Data.Array.Parallel.Stream)

2010-05-16 Thread Mark Wassell



Roman Leshchinskiy wrote:

On 16/05/2010, at 11:54, Mark Wassell wrote:

  

Hi,

This possibly might go against the spirit of what Stream programming is about 
but I having difficulties converting an imperative algorithm [1] into Haskell 
and think it would be easier if I was able to write it in a monadic style with 
operations to read and write from and to the streams.

I first tried to approach it by delving into the innards of other Stream 
functions to devise what I needed. I only got so far and the sticking point was 
defining the Monad. I then approached it from the Monad side and although what 
I have is workable, it probably isn't going to perform (for one it uses 
fromStream and tailS on each read off the front of the stream).



Data.Array.Parallel.Stream serves only one purpose: to represent loops produced by 
DPH in such a way that the compiler is able to optimise them well. Putting a monad 
on top of that will very very likely break this. To be honest, I'm not sure why 
you need the monad anyway. I would expect compression/decompression to be pure 
functions of type Stream Word8 - Stream Word8.

In any case, I would urgently recommend not to use Data.Array.Parallel.Stream 
for anything at this point. This whole subsystem will soon die of old age and 
be replaced by the much nicer stuff from package vector, specifically 
Data.Vector.Fusion.Stream and Data.Vector.Fusion.Stream.Monadic. Note that the 
latter implements monadic streams as described in 
http://www.cse.unsw.edu.au/~rl/publications/recycling.html. Perhaps those can 
be useful for you if you really need a monad.

Roman
  
Thanks. No, I don't need a Monad and I suspected it was a bad idea. It 
was really needed for convenience as all I had to go on was a C 
implementaiton of arithmetic coding (which included a getc part-way 
through the code block which I hoped to map to something like a get from 
the stream).  However thanks to Stephen I have something better to work 
from. I will also take a look at Data.Vector.Fusion.Stream.


Cheers

Mark

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


Re: [Haskell-cafe] [reactive] A pong and integrate

2010-05-16 Thread Limestraël
Why isn't it possible to make a Pong with Reactive? Where is the problem?
Conceptually, I don't see where it is. IMO, it's a time-leak issue due to a
Reactive bug, but it is not a limitation of Reactive.
I mean, it's not that it *can't* work, it's that it *should* work, shouldn't
it?

And why would it be more possible with Yampa?
I've already checked Yampa, but I find it much less simple and easy to use
than Reactive.
Moreover, I tried the space invaders sample (the sample that the paper
Yampa Arcade is about), and it lauches but it is completely unusable (I do
have a decent PC, and I get like 5fps and a gun which absolutely doesn't
move correctly). Not very appealing ^^, but maybe the problem is with the
code of the game itself or with my PC, not with Yampa...

I did not look thoroughly at elerea, but at least, when I tried its sample
dungeons of wor it worked properly ;)
I will have a look...

2010/5/16 Peter Verswyvelen bugf...@gmail.com

 As far as I know, it was never possible to make a pong game in
 Reactive, at least not with the versions I tried, but I admit a lot of
 never versions got released since then. It would be great to see one
 though :)

 You might want to try Yampa, that works for sure (although you should
 mark all your output data strict, as is done in the examples,
 otherwise you might also get space leaks or shaky frame rates). Or
 Elerea, which comes with a breakout game.

 On Sun, May 16, 2010 at 9:30 PM, Limestraël limestr...@gmail.com wrote:
  Eventually, I don't think it is a profiling issue.
  Maybe a problem with integral. According to a quite recent post on the
  reactive mailing list, the following minimal code produces the same
 problem
  :
 
  import FRP.Reactive
 
  import FRP.Reactive.LegacyAdapters
 
  import Control.Applicative
 
  type Velocity = Double
  type Position = Double
 
  data Car = Car { vel :: Velocity, pos :: Position } deriving Show
 
 
  velocity :: Behavior Velocity
 
  velocity = 1
 
  position :: Behavior Position
  position = integral (atTimes [0, 0.5 ..]) velocity
 
  car :: Behavior Car
  car = Car $ velocity * position
 
 
 
  main :: IO ()
  main = adaptE $ print $ car `snapshot_` atTimes [0, 0.5..]
 
  1) why is the leak happen?
  2) how can I fix this problem?
 
  Some more detailed informations:
 
 
  * reactive 0.11.4
  * GHC 6.12.1
  * Gentoo Linux (2.6.32-tuxonice, x86_64) or Ubuntu 9.10 64bits
  * compiled with or without -O2 flag
 
  2010/5/16 David Leimbach leim...@gmail.com
 
 
  On Sat, May 15, 2010 at 8:42 AM, Limestraël limestr...@gmail.com
 wrote:
 
  Okay,
  guess I'll have to bring out the chapter 25 of my Real World Haskell...
 
  I find it's often the most practical chapter that I hit a lot during
  writes and changes to my server process I have in Haskell in our control
  system code :-)
  That plus the information that I had missed that Control.Monad.State
  defaulted to the Lazy version (which is consistent, but for some reason
 it
  got by me) helped me to realize why I was leaking so much space in a
 garbage
  collected environment.
  I wouldn't have gotten very far with Haskell as this piece of our code
  without that chapter.  I'd love to see more writing of that sort around
  Haskell in book form.  One can become fluent in tuning Haskell by trial
 and
  error, but the sharp corners one must bump into are often sharper than
 in
  other languages I've found.
  Dave
 
 
  2010/5/15 Bulat Ziganshin bulat.zigans...@gmail.com
 
  Hello Limestraėl,
 
  Saturday, May 15, 2010, 7:02:38 PM, you wrote:
 
   But when I set my beat to tick every 60 times per second, the
   position is well updated, but I clearly see that the display
   dramatically slows down after a few seconds of execution. Too heavy
   rate for integrate?
 
  it may be due to lot of uncollected garbage that is result of lazy
  evaluation. profile program to check its GC times
 
 
  --
  Best regards,
   Bulatmailto:bulat.zigans...@gmail.com
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

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


Re: [Haskell-cafe] Numerical Analysis

2010-05-16 Thread Erik de Castro Lopo
Pierre-Etienne Meunier wrote:

 I was also wondering about how to do linear algebra : an infinite
 number of types would be needed to express all the constraints on
 matrix multiplication : we need types such as array of size m * n.
 Is there a way to generate these automatically

This is already done for you in the package hmatrix-static on 
Hackage.

Erik
-- 
--
Erik de Castro Lopo
http://www.mega-nerd.com/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [reactive] A pong and integrate

2010-05-16 Thread Peter Verswyvelen
Yes, it would be very nice to actually pinpoint why this can't be
done. Is it a bug, is it a design flaw, ... I'm just saying that I'm
not aware of a working Pong game in Reactive. Well actually, someone
did make a Tetris game with it once...

Intuitively I would say Reactive gives the programmer too much power
of what can be done with time, making it all too easy to break
causality. And since that's a physical law that can't be broken
(unless Reactive would create a wormhole somehow), it means you too
easily get delays or deadlocks. But that's just an intuition, I can't
describe this formally. This is a general problem of first class
signals IMHO: too open, not restrictive enough. First class signals
are fine for just animation, but not for complex reactivity.

Yampa gives you access to signal transformers, not the signals
themselves, which is more natural to me as a casual game developer.
Yampa looks like dataflow programming, but I agree that's not
something you want to do in a text editor ;-) (stuff like x - f - y
is easier in a graphical boxes/links editor). Also, a lot of global
state needs to be transfered to all the signal functions (e.g. a
random number seed that can't be used statically, e.g. in dynamic
collections), and an arrow is fine for that, just like a state monad
is.

Well, at least that's what I understand from it. But I understand only
tiny bits of pieces of it all :)

On Sun, May 16, 2010 at 11:41 PM, Limestraël limestr...@gmail.com wrote:
 Why isn't it possible to make a Pong with Reactive? Where is the problem?
 Conceptually, I don't see where it is. IMO, it's a time-leak issue due to a
 Reactive bug, but it is not a limitation of Reactive.
 I mean, it's not that it can't work, it's that it should work, shouldn't it?

 And why would it be more possible with Yampa?
 I've already checked Yampa, but I find it much less simple and easy to use
 than Reactive.
 Moreover, I tried the space invaders sample (the sample that the paper
 Yampa Arcade is about), and it lauches but it is completely unusable (I do
 have a decent PC, and I get like 5fps and a gun which absolutely doesn't
 move correctly). Not very appealing ^^, but maybe the problem is with the
 code of the game itself or with my PC, not with Yampa...

 I did not look thoroughly at elerea, but at least, when I tried its sample
 dungeons of wor it worked properly ;)
 I will have a look...

 2010/5/16 Peter Verswyvelen bugf...@gmail.com

 As far as I know, it was never possible to make a pong game in
 Reactive, at least not with the versions I tried, but I admit a lot of
 never versions got released since then. It would be great to see one
 though :)

 You might want to try Yampa, that works for sure (although you should
 mark all your output data strict, as is done in the examples,
 otherwise you might also get space leaks or shaky frame rates). Or
 Elerea, which comes with a breakout game.

 On Sun, May 16, 2010 at 9:30 PM, Limestraël limestr...@gmail.com wrote:
  Eventually, I don't think it is a profiling issue.
  Maybe a problem with integral. According to a quite recent post on the
  reactive mailing list, the following minimal code produces the same
  problem
  :
 
  import FRP.Reactive
 
  import FRP.Reactive.LegacyAdapters
 
  import Control.Applicative
 
  type Velocity = Double
  type Position = Double
 
  data Car = Car { vel :: Velocity, pos :: Position } deriving Show
 
 
  velocity :: Behavior Velocity
 
  velocity = 1
 
  position :: Behavior Position
  position = integral (atTimes [0, 0.5 ..]) velocity
 
  car :: Behavior Car
  car = Car $ velocity * position
 
 
 
  main :: IO ()
  main = adaptE $ print $ car `snapshot_` atTimes [0, 0.5..]
 
  1) why is the leak happen?
  2) how can I fix this problem?
 
  Some more detailed informations:
 
 
  * reactive 0.11.4
  * GHC 6.12.1
  * Gentoo Linux (2.6.32-tuxonice, x86_64) or Ubuntu 9.10 64bits
  * compiled with or without -O2 flag
 
  2010/5/16 David Leimbach leim...@gmail.com
 
 
  On Sat, May 15, 2010 at 8:42 AM, Limestraël limestr...@gmail.com
  wrote:
 
  Okay,
  guess I'll have to bring out the chapter 25 of my Real World
  Haskell...
 
  I find it's often the most practical chapter that I hit a lot during
  writes and changes to my server process I have in Haskell in our
  control
  system code :-)
  That plus the information that I had missed that Control.Monad.State
  defaulted to the Lazy version (which is consistent, but for some reason
  it
  got by me) helped me to realize why I was leaking so much space in a
  garbage
  collected environment.
  I wouldn't have gotten very far with Haskell as this piece of our code
  without that chapter.  I'd love to see more writing of that sort around
  Haskell in book form.  One can become fluent in tuning Haskell by trial
  and
  error, but the sharp corners one must bump into are often sharper than
  in
  other languages I've found.
  Dave
 
 
  2010/5/15 Bulat Ziganshin bulat.zigans...@gmail.com
 
  Hello Limestraėl,

Re: [Haskell-cafe] executeFile failing on macosx

2010-05-16 Thread David Powell
On Mon, May 17, 2010 at 1:33 AM, Bulat Ziganshin
bulat.zigans...@gmail.comwrote:

 Hello David,

 Sunday, May 16, 2010, 7:18:29 PM, you wrote:

  executeFile is failing for me on Mac OS X 10.5.8, with ghc 6.12.1
  when compiling with -threaded.  Compiling without -threaded, or running
 on linux is fine.
   forkProcess $ executeFile /bin/echo False [Ok] Nothing

 afair, forkProcess and -threaded shouldn't work together on any Unix.
 can you try forkIO or forkOS instead?


Hi Bulat,

Both, forkIO and forkOS fail in the same way for me with -threaded.  I
believe this is because macosx requires the process to only have a single
thread when doing an execv(), which I thought was the purpose of
forkProcess?

Cheers,

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


Re: [Haskell-cafe] executeFile failing on macosx

2010-05-16 Thread Thomas Schilling
Works fine on 10.6.3.  If you run with +RTS -N2, though, you'll get
forking not supported with +RTS -Nn greater than 1

The reason for this is that forking won't copy over the threads which
means that the Haskell IO manager stops working (you'd have to somehow
reinitialise the RTS while leaving heap and runtime stacks in tact --
very tricky).

I'm using http://hackage.haskell.org/package/process to run external
processes.  I haven't had any problems with it.

On 17 May 2010 00:06, David Powell da...@drp.id.au wrote:

 On Mon, May 17, 2010 at 1:33 AM, Bulat Ziganshin bulat.zigans...@gmail.com
 wrote:

 Hello David,

 Sunday, May 16, 2010, 7:18:29 PM, you wrote:

  executeFile is failing for me on Mac OS X 10.5.8, with ghc 6.12.1
  when compiling with -threaded.  Compiling without -threaded, or
  running on linux is fine.
   forkProcess $ executeFile /bin/echo False [Ok] Nothing

 afair, forkProcess and -threaded shouldn't work together on any Unix.
 can you try forkIO or forkOS instead?


 Hi Bulat,

 Both, forkIO and forkOS fail in the same way for me with -threaded.  I
 believe this is because macosx requires the process to only have a single
 thread when doing an execv(), which I thought was the purpose of
 forkProcess?

 Cheers,

 -- David

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





-- 
Push the envelope.  Watch it bend.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ShowList magic

2010-05-16 Thread Abby Henríquez Tejera
Hi.

I'm a Haskell newbie and there's a bit of Haskell code that I don't
understand how it works. In the prelude, defining the class Show, the
function showList is implemented twice, one for String and another one
for other lists:

showList cs = showChar '' . showl cs
 where showl= showChar ''
   showl ('':cs) = showString \\\ . showl cs
   showl (c:cs)   = showLitChar c . showl cs

and



showList []   = showString []
showList (x:xs)   = showChar '[' . shows x . showl xs
where showl [] = showChar ']'
  showl (x:xs) = showChar ',' . shows x .
 showl xs

The thing is... how does Haskell «know» which to execute? It works
even for the blank string:
Prelude show 
\\
Prelude show []
[]

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


Re: [Haskell-cafe] What makes Haskell difficult as .NET?

2010-05-16 Thread Richard O'Keefe

On May 15, 2010, at 5:40 AM, Daryoush Mehrtash wrote:
the speaker talks about F# on .Net platform.   Early on in the talk  
he says that they did F# because haskell would be hard to make as  
a .Net language.Does anyone know what features of Haskell make  
it difficult as .Net language?


Laziness is the obvious one:  a plain integer type in an ML-like  
language
can map directly onto a .Net primitive value type, whereas Int in  
Haskell

has to map onto something boxed.

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


Re: [Haskell-cafe] executeFile failing on macosx

2010-05-16 Thread David Powell
Indeed System.Process does work for me.  I had avoided it because it is a
little more awkward to use it when you want the actual PIDs.  I don't
understand why System.Process.runProcess works for me, but executeFile does
not.  I did find this issue (for python)
http://bugs.python.org/issue6800which I think is the same thing I'm
hitting and they also claim it is fixed
in macosx 10.6.

Anyway, I'll work with System.Process for now.  Thanks for your help.

-- David

On Mon, May 17, 2010 at 9:41 AM, Thomas Schilling
nomin...@googlemail.comwrote:

 Works fine on 10.6.3.  If you run with +RTS -N2, though, you'll get
 forking not supported with +RTS -Nn greater than 1

 The reason for this is that forking won't copy over the threads which
 means that the Haskell IO manager stops working (you'd have to somehow
 reinitialise the RTS while leaving heap and runtime stacks in tact --
 very tricky).

 I'm using http://hackage.haskell.org/package/process to run external
 processes.  I haven't had any problems with it.

 On 17 May 2010 00:06, David Powell da...@drp.id.au wrote:
 
  On Mon, May 17, 2010 at 1:33 AM, Bulat Ziganshin 
 bulat.zigans...@gmail.com
  wrote:
 
  Hello David,
 
  Sunday, May 16, 2010, 7:18:29 PM, you wrote:
 
   executeFile is failing for me on Mac OS X 10.5.8, with ghc 6.12.1
   when compiling with -threaded.  Compiling without -threaded, or
   running on linux is fine.
forkProcess $ executeFile /bin/echo False [Ok] Nothing
 
  afair, forkProcess and -threaded shouldn't work together on any Unix.
  can you try forkIO or forkOS instead?
 
 
  Hi Bulat,
 
  Both, forkIO and forkOS fail in the same way for me with -threaded.  I
  believe this is because macosx requires the process to only have a single
  thread when doing an execv(), which I thought was the purpose of
  forkProcess?
 
  Cheers,
 
  -- David
 
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 



 --
 Push the envelope.  Watch it bend.

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


Re: [Haskell-cafe] ShowList magic

2010-05-16 Thread Ivan Miljenovic
On 17 May 2010 12:56, Abby Henríquez Tejera parad...@gmail.com wrote:
 I'm a Haskell newbie and there's a bit of Haskell code that I don't
 understand how it works. In the prelude, defining the class Show, the
 function showList is implemented twice, one for String and another one
 for other lists:

    showList cs = showChar '' . showl cs
                 where showl        = showChar ''
                       showl ('':cs) = showString \\\ . showl cs
                       showl (c:cs)   = showLitChar c . showl cs

This is the default implementation; if an instance doesn't define
showList then this value is used.

    showList []       = showString []
    showList (x:xs)   = showChar '[' . shows x . showl xs
                        where showl []     = showChar ']'
                              showl (x:xs) = showChar ',' . shows x .
                                             showl xs

This is how the Show instance for Char defines showList (i.e. it
overrides the default one).

There would then be something like:

instance (Show a) = Show [a] where
show = showList

So, depending on the type used, it will either use the special ..
method (for String = [Char]) or the default one (or another special
one if another data type overrides the default implementation for
Show).

See http://book.realworldhaskell.org/read/using-typeclasses.html for
more information.

-- 
Ivan Lazar Miljenovic
ivan.miljeno...@gmail.com
IvanMiljenovic.wordpress.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] ANN: cil-0.0.1

2010-05-16 Thread Tom Hawkins
CIL [1] is an OCaml library that parses and compiles C down to a
simplified subset to ease different forms of static analysis.  Frama-C
[2] augments CIL with a property specification language (ACSL), which
can capture design contracts for C functions.  Frama-C's Jessie plugin
uses the Why [3] software verification platform, which itself uses
several different SMT solvers and proof assistances to verify ACSL
function contracts -- a very cool platform, I encourage anyone
interested in the verification of C programs to check it out.

This Hackage library [4] is an interface to the Frama-C environment.
Specifically, it provides equivalent CIL and ACSL data types, allowing
CIL and ACSL based analyzers to be written in Haskell.

The library installs a Frama-C/OCaml plugin, which dumps the CIL
database into Haskell.  Internally, both the OCaml and Haskell sides
of the interface are generated by a script (GenCIL.hs) that parses the
contents of the CIL type definitions (cil_types.mli).

Currently it only works for the most basic C programs.  A bug in
either the generated OCaml plugin or Frama-C causes issues [5].

-Tom


[1] http://cil.sourceforge.net/
[2] http://frama-c.com/
[3] http://why.lri.fr/
[4] http://hackage.haskell.org/package/cil
[5] http://bts.frama-c.com/view.php?id=481
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe