Re: [Haskell-cafe] Name overloading

2010-01-14 Thread Cristiano Paris
I wish to thank all of you for your comments. In fact, the solutions you proposed mostly coincided with mine (including the one using type families) but, in my opinion, they are more cumbersome than the prefixed names solution. Going back to my example: f x = open $ open x where: data Foo = {

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Evan Laforge
Wow, that's kind of cute: {-# LANGUAGE UnicodeSyntax #-} (*) = (*) (/) = (/) 公式 高 中 低=高*中*低/整數 整數 = 123 Oddly, if I change the order of these definitions I get syntax errors. Very mysterious. Nice how it knows that * is a symbol, but I'm not sure how I'm supposed to name a type. It certainly

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Nicolas Pouillard
Excerpts from Jinjing Wang's message of Thu Jan 14 01:28:31 +0100 2010: | The hyena backend is essentially just a translator between hack and | wai, i failed to finished it since I can't understand iteratee | (seriously) and eventually got distracted ... If I have well understood you miss a

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Pasqualino Titto Assini
Hi Michael, no, the message was not meant to be off-list, that was just me pressing the wrong button :-) Regarding happstack, I do not believe that there is a contrast with your effort, the core of happstack is in its persistency mechanism not in its http interface so I think it would be great

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Roel van Dijk
2010/1/14 Evan Laforge qdun...@gmail.com: Wow, that's kind of cute: {-# LANGUAGE UnicodeSyntax #-} (*) = (*) (/) = (/) 公式 高 中 低 = 高 * 中 * 低 / 整數 整數 = 123 That code snippet is also perfectly legal Haskell without the UnicodeSyntax language extension. You use UnicodeSyntax if you want to

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Alberto G. Corona
2010/1/14 Jinjing Wang nfjinj...@gmail.com Hyena is especially tuned for streaming and that's exactly what hack can't do (in practice). Isn't possible to stream an (almost) infinite bytestring trough hack?. I ever trough that the laziness of haskell is a great advantage in Web applications.

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Michael Snoyman
On Thu, Jan 14, 2010 at 12:50 PM, Alberto G. Corona agocor...@gmail.comwrote: 2010/1/14 Jinjing Wang nfjinj...@gmail.com Hyena is especially tuned for streaming and that's exactly what hack can't do (in practice). Isn't possible to stream an (almost) infinite bytestring trough hack?. I

Re: [Haskell-cafe] Re: FASTER primes

2010-01-14 Thread Daniel Fischer
Am Donnerstag 14 Januar 2010 08:25:48 schrieb Will Ness: Daniel Fischer daniel.is.fischer at web.de writes: Am Mittwoch 13 Januar 2010 10:43:42 schrieb Heinrich Apfelmus: I wonder whether it's really the liveness of  pair  in   mergeSP (a,b) pair      = let sm = spMerge b (fst pair)

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Malcolm Wallace
I still get the undefined reference errors. It is likely there is some combination of other mistakes as well then. Other responses have made suggestions of fixes you require in the C++ code for instance. You will need those as well. I did eventually get ghc to compile Main.hs by

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Daniel Fischer
Am Donnerstag 14 Januar 2010 11:38:57 schrieb Roel van Dijk: I was a bit surprised that you could use * as an operator since it is a punctuation character. Maybe there are some corner cases with fullwidth characters or with composition of characters. Thus speaketh the report

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Alberto G. Corona
2010/1/14 Michael Snoyman mich...@snoyman.com Well, for one thing, you'd need to use lazy IO to achieve your goal, which has some safety issues. As things get more and more complex, the requirements of lazy IO will continue to grow. This also has implications for number of open file handles

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Michael Snoyman
On Thu, Jan 14, 2010 at 1:20 PM, Alberto G. Corona agocor...@gmail.comwrote: 2010/1/14 Michael Snoyman mich...@snoyman.com Well, for one thing, you'd need to use lazy IO to achieve your goal, which has some safety issues. As things get more and more complex, the requirements of lazy IO

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Roel van Dijk
Thus speaketh the report (http://haskell.org/onlinereport/lexemes.html): symbol   -      ascSymbol | uniSymbolspecial | _ | : | | ' ascSymbol       -      ! | # | $ | % | | * | + | . | / | | = | | ? | @        |       \ | ^ | | | - | ~ uniSymbol        -      any Unicode symbol or

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Colin Paul Adams
Roel == Roel van Dijk vandijk.r...@gmail.com writes: Roel I think it is time for an Obfuscated Haskell Contest :-) Are you allowed to use obsolete scripts for your identifiers? :-) -- Colin Adams Preston Lancashire ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Roel van Dijk
On Thu, Jan 14, 2010 at 12:47 PM, Colin Paul Adams co...@colina.demon.co.uk wrote: Roel == Roel van Dijk vandijk.r...@gmail.com writes:    Roel I think it is time for an Obfuscated Haskell Contest :-) Are you allowed to use obsolete scripts for your identifiers? :-) Sure, I'll consider bonus

Re: [Haskell-cafe] Typed Configuration Files

2010-01-14 Thread Ketil Malde
Magnus Therning mag...@therning.org writes: Seriously, cmdargs is *brilliant*. It's also magic (to me). On this list, I'm uncertain whether brilliant is a warning or a recommendation, but magic is clearly irresistible, so I had a go at using cmdargs. And I agree, it is really nice in quickly

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Michael Snoyman
On Thu, Jan 14, 2010 at 1:58 PM, Alberto G. Corona agocor...@gmail.comwrote: 2010/1/14 Michael Snoyman mich...@snoyman.com On Thu, Jan 14, 2010 at 1:20 PM, Alberto G. Corona agocor...@gmail.comwrote: 2010/1/14 Michael Snoyman mich...@snoyman.com Well, for one thing, you'd need to

[Haskell-cafe] ANN: hakyll-1.0

2010-01-14 Thread Jasper Van der Jeugt
Hello, I have just released hakyll[1] 1.0. It is now available on hackage[2]. This is considered a first stable release (hence 1.0), and pretty it is functional. Hakyll is a Haskell library for generating static sites. It is written in a very configurable way and uses an xmonad-like DSL for

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Martijn van Steenbergen
Niklas Broberg wrote: Haskell '98 apparently features 25 reserved words. (Not counting forall and mdo and so on, which AFAIK are not in Haskell '98.) 21 actually. case, class, data, default, deriving, do, else, if, import, in, infix, infixl, infixr, instance, let, module, newtype, of, then,

Re: [Haskell-cafe] wildcards for type variables?

2010-01-14 Thread Ozgur Akgun
Can someone give an example of a reasonable function that never uses one of its parameters, and justify the existence of that parameter in this case, please? Because for this example, f :: _unused - A - B f _ a = b I think what I'd do is to write the function f without that first parameter, and

Re: [Haskell-cafe] wildcards for type variables?

2010-01-14 Thread Ivan Lazar Miljenovic
Ozgur Akgun ozgurak...@gmail.com writes: Can someone give an example of a reasonable function that never uses one of its parameters, and justify the existence of that parameter in this case, please? I would like to bring your attention to the const function: , | const :: a - b - a |

Re: [Haskell-cafe] wildcards for type variables?

2010-01-14 Thread Ketil Malde
Ozgur Akgun ozgurak...@gmail.com writes: Can someone give an example of a reasonable function that never uses one of its parameters, and justify the existence of that parameter in this case, please? E.g, 'const' is useful when you need something to feed to a higher order function: -- an

[Haskell-cafe] deleteBy type too restrictive

2010-01-14 Thread Dan Rosén
Hello, I realized today that the type for deleteBy in Data.List is too restrictive. The code is: deleteBy:: (a - a - Bool) - a - [a] - [a] deleteBy _ _ []= [] deleteBy eq x (y:ys)= if x `eq` y then ys else y : deleteBy eq x ys though the type deleteBy :: (b - a -

[Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Ian675
Hi, First of all, sorry if its in the wrong section.. But I'm just having trouble getting to grips with Haskell. I have my functional programming exam tommorow and I'm struggling to understand any of this. We worked through the book The Craft Of Functional Programming and Im trying to work my

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Niklas Broberg
Since you can define operators in Haskell, would it make sense to include '=', '--', ':', ',' etc. as reserved names since those can't be used as operator names? They are indeed reserved operators in the report. 11 of those: .. : :: = \ | - - @ ~ = To be fair, _ is also a reserved

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Tom Tobin
On Thu, Jan 14, 2010 at 12:45 AM, Colin Paul Adams co...@colina.demon.co.uk wrote: Tom == Tom Tobin korp...@korpios.com writes:    Tom readability.  The ASCII characters are universal and easily    Tom recognized No they are not. My wife is Chinese. When she was learning pinyin as a child,

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Martin Coxall
But after that im lost :( Is there any general advice? Just keep reading the book till it drills into my big head? Is it that you're having difficulty knowing how you'd solve certain classes of problems using Haskell? You're stuck in an imperative rut? The O'Reilly book Real World

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Matthias Görgens
Hi, it may be a bit too late for you, but in general working through Smullyan's To Mock a Mockingbird (http://en.wikipedia.org/wiki/To_Mock_a_Mockingbird) may help in coming to grips with some of the theory (and intuition) behind functional programming. The Real World Haskell book is also a good

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Ian675
Pretty much yeah.. Im going through the book and things like : Define a function rangeProduct which when given natural numbers m and n, returns the product m*(m+1)**(n-1)*n I got the solution from my lecture notes but I still dont understand it.. rangeProduct :: Int - Int - Int

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Ian675
It may be a bit late but I'll try anything Thankyou, I'll have a read :-) Matthias Görgens-2 wrote: Hi, it may be a bit too late for you, but in general working through Smullyan's To Mock a Mockingbird (http://en.wikipedia.org/wiki/To_Mock_a_Mockingbird) may help in coming to grips

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Tom Tobin
On Thu, Jan 14, 2010 at 7:52 AM, Ian675 adam_khan_...@hotmail.com wrote: Is there any general advice? Just keep reading the book till it drills into my big head? Also don't be afraid to ask specific questions on the Beginners mailing list; while Cafe is a good general resource, Beginners is

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Matthias Görgens
All Lisps have special forms which are evaluated uniquely and differently from function application and are therefore reserved words by another name. For example, Clojure has def, if, do, let, var, quote, fn, loop, recur, throw, try, monitor-enter, monitor-exit, dot, new and set!. Yes, but

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Martin Coxall
On 14 Jan 2010, at 14:42, Matthias Görgens wrote: All Lisps have special forms which are evaluated uniquely and differently from function application and are therefore reserved words by another name. For example, Clojure has def, if, do, let, var, quote, fn, loop, recur, throw, try,

Re: [Haskell-cafe] Typed Configuration Files

2010-01-14 Thread Ketil Malde
Ketil Malde ke...@malde.org writes: - CmdArgs helpfully provides default --help, --version as well as --quite and --verbose. For the two former, there's also a nice default implementation, but presumably the latter two are for use in the program proper. Unfortunately, I don't know how

Re: [Haskell-cafe] Re: looking for origin of quote on preprocessors and language design

2010-01-14 Thread Henning Thielemann
Maciej Piechotka schrieb: Hmm. May I ask how to do for example something depending on POSIX or WinAPI? I am sorry but I cannot see how any of the above problems could be solved. Sure, I choose different Hs-Source-Dirs for the different platforms. Multiple Hs-Source-Dirs are merged.

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Steve Schafer
On Thu, 14 Jan 2010 14:42:06 +, you wrote: All Lisps have special forms which are evaluated uniquely and differently from function application and are therefore reserved words by another name. For example, Clojure has def, if, do, let, var, quote, fn, loop, recur, throw, try,

[Haskell-cafe] Quick, somebody do something!

2010-01-14 Thread Henk-Jan van Tuyl
Haskell has dropped out of the top 50 at Tiobe [1]; how could this hapen? Let's start selling mobile phones that can only be programmed in Haskell :-) [1] http://www.tiobe.com/content/paperinfo/tpci/index.html -- Met vriendelijke groet, Henk-Jan van Tuyl -- http://Van.Tuyl.eu/

Re: [Haskell-cafe] Quick, somebody do something!

2010-01-14 Thread Deniz Dogan
2010/1/14 Henk-Jan van Tuyl hjgt...@chello.nl: Haskell has dropped out of the top 50 at Tiobe [1]; how could this hapen? Let's start selling mobile phones that can only be programmed in Haskell :-) [1] http://www.tiobe.com/content/paperinfo/tpci/index.html -- Met vriendelijke groet,

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Jeremy Shaw
Hello, Happstack is currently bundled with it's own lazy I/O based HTTP backend. Ideally, we would like to split that out, and allow happstack to be used with that backend, hyena, or other options. A primary using for using hyena would be for the benefits of predictability and constant

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread DNM
OK. Before anyone expends any e-ink replying to my reply below -- the one where I demonstrate that I don't understand what -c, -cpp mean to 'ghc' (not that you can blame me, since there isn't any documentation in the 'ghc' man page) -- I see why the Main.o file doesn't run. It's an object file,

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Henk-Jan van Tuyl
On Thu, 14 Jan 2010 15:38:26 +0100, Ian675 adam_khan_...@hotmail.com wrote: Pretty much yeah.. Im going through the book and things like : Define a function rangeProduct which when given natural numbers m and n, returns the product m*(m+1)**(n-1)*n I got the solution from my lecture

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Stephen Tetley
Hello Does you find this version easier to understand? rangeProduct :: Int - Int - Int rangeProduct m n = if m n then 0 else if m == n then m else m * rangeProduct (m+1) n I would suspect the main point of the example is

Re: [Haskell-cafe] Web application interface

2010-01-14 Thread Michael Snoyman
On Thu, Jan 14, 2010 at 5:42 PM, Jeremy Shaw jer...@n-heptane.com wrote: Hello, Happstack is currently bundled with it's own lazy I/O based HTTP backend. Ideally, we would like to split that out, and allow happstack to be used with that backend, hyena, or other options. A primary using for

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Evan Laforge
Unicode identifiers are fun but this is a good point.  The line has to be somewhere, so it might as well be in the historical position unless there are widely agreed on benefits to moving it. I have already crossed that line: Ha, well haskell programmers wouldn't be haskell programmers if

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Ian675
thankyou.. that made more sense to me :) What im doing now is.. Im still working through the Craft of Functional Programming book but I've found a site that has solutions to some of the excercise questions. So i'm noting them down and trying to make sense of them Is that a good approach?

[Haskell-cafe] Haskell implementation of ideas from StandardML as a Metaprogramming language

2010-01-14 Thread CK Kashyap
Hi All, I was just going over the paper titled - Standard ML as a meta programming language by Samuel Kamin - It has a few ideas of generating C++ code from ML. The first one being generating C++ top down parser. I wanted to try out the sample in Haskell - I was wondering if anyone's already

Re: [Haskell-cafe] Re: looking for origin of quote on preprocessors and language design

2010-01-14 Thread Jason Dusek
2010/01/07 Maciej Piechotka uzytkown...@gmail.com: On Thu, 2010-01-07 at 13:32 +0100, Johannes Waldmann wrote: Dear all, It's not exactly Haskell-specific, but ... I am trying to track down the origin of the proverb the existence (or: need for) a preprocessor shows omissions in (the

Re: [Haskell-cafe] Typed Configuration Files

2010-01-14 Thread Matthias Görgens
Hi Sebastian, You might also want to look at how xmonad handles it's configuration. Basically the configuration file is the main-file that produces the executable and takes in the rest of xmonad as a library. This works out quite well, but you need a compiler to update the configuration.

Re: [Haskell-cafe] Typed Configuration Files

2010-01-14 Thread Neil Mitchell
Hi The CmdArgs manual might help: http://community.haskell.org/~ndm/darcs/cmdargs/cmdargs.htm Seriously, cmdargs is *brilliant*.  It's also magic (to me). On this list, I'm uncertain whether brilliant is a warning or a recommendation, but magic is clearly irresistible, so I had a go at

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Gregory Crosswhite
Yes. An approach that I have always used that has worked well for me is to keep a list of tricks while I am studying. Whenever I get stuck on a practice problem but eventually figure it out (either by simply thinking harder, looking it up, or asking someone for help), I try to identify the

Re: [Haskell-cafe] sizeOf on a type

2010-01-14 Thread Henning Thielemann
On Fri, 25 Dec 2009, Lennart Augustsson wrote: sizeOfPtr :: Ptr a - Int sizeOfPtr = sizeOf . (undefined :: Ptr a - a) No need for scoped type variables. But it does assume sizeOf does not use its argument. That's even better. I'll add that to the Wiki.  

Re: [Haskell-cafe] wildcards for type variables?

2010-01-14 Thread Evan Laforge
On Thu, Jan 14, 2010 at 5:19 AM, Ozgur Akgun ozgurak...@gmail.com wrote: Can someone give an example of a reasonable function that never uses one of its parameters, and justify the existence of that parameter in this case, please? As I mentioned, this is not only about parameters, but about

Re: [Haskell-cafe] Haskell implementation of ideas from StandardML as a Metaprogramming language

2010-01-14 Thread Stephen Tetley
Hello Kashyap I can do MSL and Region, maybe I did the parser combinators but I can't find them at the moment. I tried to keep the code close to the original SML, so as Haskell code its not pretty. Not having quasiquote was a problem. Best wishes Stephen

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread Andrew Coppin
Martijn van Steenbergen wrote: Niklas Broberg wrote: 21 actually. case, class, data, default, deriving, do, else, if, import, in, infix, infixl, infixr, instance, let, module, newtype, of, then, type, where. There's also three special words that can still be used as identifiers, so aren't

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread DNM
Which is weird, because 'srilm.o'/'srilm.h' are the files that define the mysterious undefined references. I'll keep plugging away and report back when (or whether) I make some progress. In the meanwhile, if anyone has a clue, I'm all ears. Best, D.N. Malcolm Wallace wrote: However, if

Re: [Haskell-cafe] Language simplicity

2010-01-14 Thread jur
On Jan 14, 2010, at 8:38 PM, Andrew Coppin wrote: Martijn van Steenbergen wrote: Niklas Broberg wrote: 21 actually. case, class, data, default, deriving, do, else, if, import, in, infix, infixl, infixr, instance, let, module, newtype, of, then, type, where. There's also three special words

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Daniel Fischer
Am Donnerstag 14 Januar 2010 20:42:42 schrieb DNM: Which is weird, because 'srilm.o'/'srilm.h' are the files that define the mysterious undefined references. I'll keep plugging away and report back when (or whether) I make some progress. In the meanwhile, if anyone has a clue, I'm all ears.

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Paulo Tanimoto
On Thu, Jan 14, 2010 at 2:08 PM, Daniel Fischer daniel.is.fisc...@web.de wrote: Just an idea. Are you on windows? If so, then your foreign calls would probably have to be foreign import stdcall srilm.h whatever ... instead of foreign import ccall ... Yes, I came here to say that too. I

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Stephen Tetley
Hello Daniel On Windows, isn't stdcall vs ccall still dependent on the actual library and what compiled it - commonly MSVC (stdcall) or gcc (ccall) of course? I could very easily be wrong... Best wishes Stephen 2010/1/14 Daniel Fischer daniel.is.fisc...@web.de: Am Donnerstag 14 Januar

Re[2]: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Bulat Ziganshin
Hello Daniel, Thursday, January 14, 2010, 11:08:24 PM, you wrote: i think you are wrong. stdcall used for std windows dlls, but gcc by default generates ccall things. and cl anyway useless here Just an idea. Are you on windows? If so, then your foreign calls would probably have to be

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread DNM
Nope. Ubuntu Linux (Intrepid Ibex). I wish it were that simple. --D.N. Daniel Fischer-4 wrote: Am Donnerstag 14 Januar 2010 20:42:42 schrieb DNM: Which is weird, because 'srilm.o'/'srilm.h' are the files that define the mysterious undefined references. I'll keep plugging away and

Re[2]: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Bulat Ziganshin
Hello DNM, Thursday, January 14, 2010, 10:42:42 PM, you wrote: there is better way rather than playing with random bits. just find tutorial on FFI, and try it. once this example works, start modifying it to learn various aspects of ffi and add functionality you need it's one thing i've learned

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Daniel Fischer
Am Donnerstag 14 Januar 2010 21:39:57 schrieb DNM: Nope. Ubuntu Linux (Intrepid Ibex). I wish it were that simple. --D.N. Okay, so it's not a borken OS 8-) Can you post ought to be compiling code? That might help locate the problem. ___

Re: Re[2]: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Stephen Tetley
2010/1/14 Bulat Ziganshin bulat.zigans...@gmail.com: there is better way rather than playing with random bits. just find tutorial on FFI, and try it. once this example works, start modifying it to learn various aspects of ffi and add functionality you need Also binding to a C library is

[Haskell-cafe] ANNOUNCE: Functional Programming Bibliography

2010-01-14 Thread James Russell
I am pleased to announce the Functional Programming Bibliography at http://www.catamorphism.net/ The functional programming bibliography was created in the hope that it will be a useful resource to the functional programming community. The site is still in an early stage of development, and is

Re: [Haskell-cafe] ANNOUNCE: Functional Programming Bibliography

2010-01-14 Thread Tim Wawrzynczak
At a quick glance, +5 Awesome. Cheers - Tim On Thu, Jan 14, 2010 at 3:03 PM, James Russell j.russ...@alum.mit.eduwrote: I am pleased to announce the Functional Programming Bibliography at http://www.catamorphism.net/ The functional programming bibliography was created in the hope that it

Re: [Haskell-cafe] ANNOUNCE: Functional Programming Bibliography

2010-01-14 Thread Tim Wawrzynczak
Oh also, I noticed that you say it's powered by Haskell. Would you mind sharing some of your architectural details as they relate to Haskell with us? On Thu, Jan 14, 2010 at 3:11 PM, Tim Wawrzynczak inforichl...@gmail.comwrote: At a quick glance, +5 Awesome. Cheers - Tim On Thu, Jan

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Miguel Mitrofanov
Works fine here (Mac OS X 10.5): MigMit:ngram MigMit$ ghc --make Main.hs srilm.o [1 of 2] Compiling LM ( LM.hs, LM.o ) LM.hs:9:0: Warning: possible missing in foreign import of FunPtr [2 of 2] Compiling Main ( Main.hs, Main.o ) Linking Main ... MigMit:ngram MigMit$ ls

Re: [Haskell-cafe] ANNOUNCE: Functional Programming Bibliography

2010-01-14 Thread Andrew Coppin
James Russell wrote: I am pleased to announce the Functional Programming Bibliography at http://www.catamorphism.net/ I am eager for suggestions as to how the site could be made more useful. As is traditional, my ISP's spam filter ate this email. *sigh* Anyway, I did a search for Simon

Re: [Haskell-cafe] Quick, somebody do something!

2010-01-14 Thread Don Stewart
While the month-old Go language makes the top 15? Methods considered unsound. hjgtuyl: Haskell has dropped out of the top 50 at Tiobe [1]; how could this hapen? Let's start selling mobile phones that can only be programmed in Haskell :-) [1]

Re: [Haskell-cafe] FFI, C/C++ and undefined references

2010-01-14 Thread Daniel Fischer
Am Donnerstag 14 Januar 2010 22:19:08 schrieb Miguel Mitrofanov: Works fine here (Mac OS X 10.5): MigMit:ngram MigMit$ ghc --make Main.hs srilm.o [1 of 2] Compiling LM               ( LM.hs, LM.o ) LM.hs:9:0: Warning: possible missing in foreign import of FunPtr [2 of 2] Compiling Main    

[Haskell-cafe] I/O performance drop in ghc 6.12.1

2010-01-14 Thread Peter Simons
Hi, I just updated to GHC 6.12.1, and I noticed a significant drop in I/O performance that I can't explain. The following code is a simple re-implementation of cat(1), i.e. it just echos all data from standard input to standard output: module Main ( main ) where import System.IO import

Re: [Haskell-cafe] I/O performance drop in ghc 6.12.1

2010-01-14 Thread Brandon S. Allbery KF8NH
On Jan 14, 2010, at 17:30 , Peter Simons wrote: I just updated to GHC 6.12.1, and I noticed a significant drop in I/O performance that I can't explain. The following code is a simple re-implementation of cat(1), i.e. it just echos all data from standard input to standard output: GHC 6.12.1

Re: [Haskell-cafe] I/O performance drop in ghc 6.12.1

2010-01-14 Thread Bryan O'Sullivan
On Thu, Jan 14, 2010 at 2:30 PM, Peter Simons sim...@cryp.to wrote: I just updated to GHC 6.12.1, and I noticed a significant drop in I/O performance that I can't explain. This is probably brought about by the new Unicode I/O support in 6.12. Your file isn't open in binary mode, so it's

[Haskell-cafe] Force -threaded from a library

2010-01-14 Thread John Van Enk
Hi List, Is it possible to prevent a library from being used unless -threaded is enabled? I have a specific case where lots-of-nasty shows up if the library is linked against an executable built without -threaded. I suppose this is GHC specific. /jve

Re: [Haskell-cafe] I/O performance drop in ghc 6.12.1

2010-01-14 Thread Svein Ove Aas
On Thu, Jan 14, 2010 at 11:38 PM, Bryan O'Sullivan b...@serpentine.com wrote: On Thu, Jan 14, 2010 at 2:30 PM, Peter Simons sim...@cryp.to wrote: I just updated to GHC 6.12.1, and I noticed a significant drop in I/O performance that I can't explain. This is probably brought about by the new

Re: [Haskell-cafe] Quick, somebody do something!

2010-01-14 Thread Alp Mestan
On Thu, Jan 14, 2010 at 11:21 PM, Don Stewart d...@galois.com wrote: While the month-old Go language makes the top 15? Methods considered unsound. I fully agree. But anyway, I don't think people either already in the haskell world or about to enter it will find this relevant. -- Alp Mestan

[Haskell-cafe] Re: I/O performance drop in ghc 6.12.1

2010-01-14 Thread Peter Simons
Hi Svein, Hold on, he's using hGetBuf/hPutBuf. exactly, that's what I was thinking. When a program requests that 'n' bytes ought to be read into memory at the location designated by the given 'Ptr Word8', how could GHC possibly do any encoding or decoding? That API doesn't allow for multi-byte

[Haskell-cafe] RFC: Space-leak-free, efficient symbol table implementation.

2010-01-14 Thread Thomas Schilling
Hello Café, Symbol tables are a very common data structure in compilers but the most common implementation uses a hash table as a global variable which results in a space leak. If we decide to use several symbol tables we still cannot join different symbol tables. After some Googling I found

[Haskell-cafe] IDL - compilers

2010-01-14 Thread Günther Schmidt
Hi, are there any IDL compilers that can create Haskelk modules from header files or type-libs? Günther ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] ANNOUNCE: Functional Programming Bibliography

2010-01-14 Thread James Russell
On Thu, Jan 14, 2010 at 4:12 PM, Tim Wawrzynczak inforichl...@gmail.com wrote: Oh also, I noticed that you say it's powered by Haskell. Would you mind sharing some of your architectural details as they relate to Haskell with us? Not much to it, really. It's a LAMH thing, if you will. The

Re: [Haskell-cafe] IDL - compilers

2010-01-14 Thread Don Stewart
gue.schmidt: Hi, are there any IDL compilers that can create Haskelk modules from header files or type-libs? The venerable hdirect. http://www.haskell.org/hdirect/ I've recently cabalized the package, which is still in fine condition. Let me know if you need a copy. -- Don

Re: [Haskell-cafe] IDL - compilers

2010-01-14 Thread Günther Schmidt
Hi Don, Am 15.01.10 02:00, schrieb Don Stewart: gue.schmidt: Hi, are there any IDL compilers that can create Haskelk modules from header files or type-libs? The venerable hdirect. http://www.haskell.org/hdirect/ I've recently cabalized the package, which is still in fine

Re: [Haskell-cafe] General Advice Needed ..

2010-01-14 Thread Richard O'Keefe
On Jan 15, 2010, at 3:38 AM, Ian675 wrote: Pretty much yeah.. Im going through the book and things like : Define a function rangeProduct which when given natural numbers m and n, returns the product m*(m+1)**(n-1)*n Case analysis and recursion. If m n, the answer is 1 (the product

Re: [Haskell-cafe] Haskell implementation of ideas from StandardML as a Metaprogramming language

2010-01-14 Thread CK Kashyap
Thank you very much Stephen ... I'll try and work on the doc plus the code you've sent to understand it. If you do find the parser combinators, please do send it to me. Thanks and Regards, Kashyap - Original Message From: Stephen Tetley stephen.tet...@gmail.com Cc:

[Haskell-cafe] ANN: Lite Haskell IDE

2010-01-14 Thread Mambo Banda
Hi Just started an open source project called Hoodoo. It is meant to be a Lite IDE for Haskell. I wrote it to learn Haskell, so if you are a beginner (like me) it might interest you. If you're interested follow this link (http://hoodoo.kenai.com/), and if you like what you see, grab the code