Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Tomasz Zielonka
On Mon, May 28, 2007 at 11:43:47AM +0100, Andrew Coppin wrote: - Chapter 2 is... puzzling. Personally I've never seen the point of trying to check a program against a specification. If you find a mismatch then which thing is wrong - the program, or the spec? Knowing that one of them is wrong

Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-29 Thread kahl
P.S. Have some cute code: Control.Monad.Fix.fix ((1:) . scanl (+) 1) Cute! But what an un-cute qualified name: :t Control.Monad.Fix.fix Control.Monad.Fix.fix :: (a - a) - a Has nothing to do with monads, and would perhaps be considered as ``out of Control'' in any case... ;-)

Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-29 Thread Donald Bruce Stewart
kahl: P.S. Have some cute code: Control.Monad.Fix.fix ((1:) . scanl (+) 1) Cute! But what an un-cute qualified name: :t Control.Monad.Fix.fix Control.Monad.Fix.fix :: (a - a) - a Has nothing to do with monads, and would perhaps be considered as ``out of

RE: [Haskell-cafe] Yet another top-level state proposal

2007-05-29 Thread Simon Peyton-Jones
At the risk of becoming repetitious, let's keep refining the Wiki to give these competing proposals in their most up-to-date form. I'm not arguing against email -- it's an excellent medium for discussion -- but having the outcomes recorded makes them accessible to a much wider audience who

[Haskell-cafe] data PLZ a

2007-05-29 Thread Donald Bruce Stewart
We got the names wrong! data PLZ a = AWSUM_THX a | O_NOES String instance Monad PLZ where return= AWSUM_THX fail = O_NOES O_NOES s= _ = O_NOES s AWSUM_THX x = f = f x Thanks to mauke on #haskell. -- Don

Re: [Haskell-cafe] data PLZ a

2007-05-29 Thread Dan Mead
is that your implementation of LOLCODE? :P On 5/29/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote: We got the names wrong! data PLZ a = AWSUM_THX a | O_NOES String instance Monad PLZ where return= AWSUM_THX fail = O_NOES O_NOES s

Re: [Haskell-cafe] data PLZ a

2007-05-29 Thread Donald Bruce Stewart
d.w.mead: is that your implementation of LOLCODE? :P On 5/29/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote: We got the names wrong! data PLZ a = AWSUM_THX a | O_NOES String instance Monad PLZ where return= AWSUM_THX

Re: [Haskell-cafe] Re: Slower with ByteStrings?

2007-05-29 Thread Mirko Rahn
from the letters of that word. A letter can be used at most as many times as it appears in the input word. So, letter can only match words with 0, 1, or 2 t's in them. frequencies = map (\x - (head x, length x)) . group . sort superset xs = \ys - let y = frequencies ys in

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Vincent Kraeutler
Donald Bruce Stewart wrote: P.S. Have some cute code: Control.Monad.Fix.fix ((1:) . scanl (+) 1) this is cute indeed! (do you keep an emergency reserve of those around for situations like this? ;-)) ever the interested amateur, i admittedly remain stumped by fix (there's evidence i'm

Re: [Haskell-cafe] The C Equiv of != in Haskell

2007-05-29 Thread David House
On 29/05/07, Daniel McAllansmith [EMAIL PROTECTED] wrote: Just in case there was some sort of miscommunication, the actual answer to your question is (/=) :: a - a - Bool, as Neil said. Almost, (/=) :: Eq a = a - a. (Just for completeness.) -- -David House, [EMAIL PROTECTED]

Re: [Haskell-cafe] The C Equiv of != in Haskell

2007-05-29 Thread Antti-Juhani Kaijanaho
On Tue, May 29, 2007 at 11:20:27AM +0100, David House wrote: Almost, (/=) :: Eq a = a - a. Well, not quite :) You forgot - Bool at the end :) (Just for completeness.) Exactly :) -- Antti-Juhani Kaijanaho, Jyväskylä http://antti-juhani.kaijanaho.fi/newblog/

Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Henning Thielemann
Hi Andrew! I share your concerns about the simplicity of the language. Once extensions exists, they are used widely, and readers of programs must understand them, also if the extensions are used without need. I understand the motivations for many type extensions, but library writers tend to use

Re: [Haskell-cafe] The C Equiv of != in Haskell

2007-05-29 Thread David House
On 29/05/07, Antti-Juhani Kaijanaho [EMAIL PROTECTED] wrote: Well, not quite :) You forgot - Bool at the end :) Ha! Sorry, what a lovely ironic typo. :) -- -David House, [EMAIL PROTECTED] ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] The C Equiv of != in Haskell

2007-05-29 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 11:20:27AM +0100, David House wrote: On 29/05/07, Daniel McAllansmith [EMAIL PROTECTED] wrote: Just in case there was some sort of miscommunication, the actual answer to your question is (/=) :: a - a - Bool, as Neil said. Almost, (/=) :: Eq a = a - a. Almost again!

Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Henning Thielemann
On Sun, 27 May 2007, Andrew Coppin wrote: Personally, I try to avoid ever using list comprehensions. Me too. Successfully, I have to add. But every now and then I discover an expression which is apparently not expressible without them - which is odd, considering they're only sugar...

Re: [Haskell-cafe] Distributing a program with support files

2007-05-29 Thread Neil Mitchell
Hi Isaac Why? If it's a binary package, the IO will return the compiled-in path, which on the same distribution/whatever, should be the correct path. In particular, on Windows, I assume that the IO returns something that is in fact relative to the current position of the executable at the

Re: [Haskell-cafe] Yet another top-level state proposal

2007-05-29 Thread Claus Reinke
At the risk of becoming repetitious, let's keep refining the Wiki to give these competing proposals in their most up-to-date form. I'm not arguing against email -- it's an excellent medium for discussion -- but having the outcomes recorded makes them accessible to a much wider audience who

Re: [Haskell-cafe] Mysterious monads

2007-05-29 Thread Henning Thielemann
On Sun, 27 May 2007, Andrew Coppin wrote: such that a Reader is created with an initial list, and the read function fetches 1 element out of that list. That is, the expression x - read will take the head element of the list and put it into x, keeping the tail to be read later. (Oh yeah -

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote: Donald Bruce Stewart wrote: P.S. Have some cute code: Control.Monad.Fix.fix ((1:) . scanl (+) 1) this is cute indeed! (do you keep an emergency reserve of those around for situations like this? ;-)) ever the

Re: [Haskell-cafe] data PLZ a

2007-05-29 Thread ajb
G'day all. Quoting Dan Mead [EMAIL PROTECTED]: is that your implementation of LOLCODE? O HAI IM IN UR CODE REDUCIN' UR REDEKZEZ BURNIN' UR MEGAHURTZ Cheers, Andrew Bromage P.S. This is harder than writing l33t. ___

[Haskell-cafe] Cabal can't install in home directory

2007-05-29 Thread Grzegorz
Hi, It seems that if GHC is installed non-user-writable directory, and you want to install a package in the home directory (using runghc Setup configure --prefix=$HOME) this isn't possible: when running runghc Setup install you get an error like this: Unable to rename

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Tomasz Zielonka
On Tue, May 29, 2007 at 02:19:31PM +0200, Tomasz Zielonka wrote: On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote: ever the interested amateur, i admittedly remain stumped by fix (there's evidence i'm not the only one [1]) The above code is equivalent to let l = 1 :

Re: [Haskell-cafe] New book: Real-World Haskell!

2007-05-29 Thread Jules Bean
Doug Kirk wrote: No offense to the darcs creators, but 1) Only current Haskellers use it; everyone else either uses Subversion or is migrating to it; If that is true, then they have missed the point. DVC is a real win for most workflows. The applicable alternatives to darcs are : bzr,

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Vincent Kraeutler
Tomasz Zielonka wrote: On Tue, May 29, 2007 at 02:19:31PM +0200, Tomasz Zielonka wrote: On Tue, May 29, 2007 at 12:15:23PM +0200, Vincent Kraeutler wrote: ever the interested amateur, i admittedly remain stumped by fix (there's evidence i'm not the only one [1]) The above

Re: [Haskell-cafe] New book: Real-World Haskell!

2007-05-29 Thread Hakim Cassimally
On 29/05/07, Jules Bean [EMAIL PROTECTED] wrote: Doug Kirk wrote: No offense to the darcs creators, but 1) Only current Haskellers use it; everyone else either uses Subversion or is migrating to it; If that is true, then they have missed the point. DVC is a real win for most workflows.

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Vincent Kraeutler
Vincent Kraeutler wrote: Tomasz Zielonka wrote: [snip] anyhow. if someone has a pedestrian's guide to the fixed point operator lying around, a link would be much appreciated. i see that dons has very recently provided an answer for this on reddit:

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Donald Bruce Stewart
vincent: i see that the definition of fix (from Control.Monad.Fix) could not be any simpler: fix f = let x = f x in x same goes for the type: Prelude :t Control.Monad.Fix.fix Control.Monad.Fix.fix :: (a - a) - a it's just that i find it difficult to get concrete intellectual

Re: [Haskell-cafe] Cabal can't install in home directory

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Grzegorz wrote: Hi, It seems that if GHC is installed non-user-writable directory, and you want to install a package in the home directory (using runghc Setup configure --prefix=$HOME) this isn't possible: when running runghc Setup install you

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread David House
On 29/05/07, Vincent Kraeutler [EMAIL PROTECTED] wrote: anyhow. if someone has a pedestrian's guide to the fixed point operator lying around, a link would be much appreciated. Here's a paraphrased quotation from Pierce's Types and Programming Languages: Suppose we want to write a recursive

[Haskell-cafe] Frisby grammars that have context

2007-05-29 Thread Mark T.B. Carroll
I've been playing with Text.Parsers.Frisby to see how it stacks against other options and, while it's been great so far, I am finding that I can't encode a grammar where what's acceptable depends on what's already been parsed in some nontrivial way. To take a simple example, imagine a grammar

[Haskell-cafe] Re: Slower with ByteStrings?

2007-05-29 Thread apfelmus
Mirko Rahn wrote: from the letters of that word. A letter can be used at most as many times as it appears in the input word. So, letter can only match words with 0, 1, or 2 t's in them. frequencies = map (\x - (head x, length x)) . group . sort superset xs = \ys - let y =

Re: [Haskell-cafe] Frisby grammars that have context

2007-05-29 Thread Mark T.B. Carroll
Actually, while I'm at it, another thing I was wondering: Text.ParserCombinators.Parsec.Char offers us nice things like `lower'. However, where's this stuff in Frisby? I could use something horrific like oneOf [filter isLower [minBound .. maxBound ]] or something, but how best to get

[Haskell-cafe] Re: Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Jon Fairbairn
Vincent Kraeutler [EMAIL PROTECTED] writes: anyhow. if someone has a pedestrian's guide to the fixed point operator lying around, a link would be much appreciated. At the risk of increasing rather than decreasing your confusion (but in the hope that once you get over it you will be

[Haskell-cafe] Re: Cabal can't install in home directory

2007-05-29 Thread Grzegorz
Isaac Dupree isaacdupree at charter.net writes: You don't have permission to install it in a way that all users of that GHC will then be able to use it. You should pass --user to runghc Setup install for your desired effect. (whereas I shouldn't because my GHC itself is also compiled by

[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
Mark T.B. Carroll wrote: I've been playing with Text.Parsers.Frisby to see how it stacks against other options and, while it's been great so far, I am finding that I can't encode a grammar where what's acceptable depends on what's already been parsed in some nontrivial way. [...] Is this

RE: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskellmiscommunication thread]

2007-05-29 Thread Bayley, Alistair
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Vincent Kraeutler anyhow. if someone has a pedestrian's guide to the fixed point operator lying around, a link would be much appreciated. Just to add to the noise... I've always quite liked Richard Gabriel's The Why of Y

RE: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Simon Peyton-Jones
| I wish the compilers would allow more fine grained switches on languages | extensions. -fglasgow-exts switches them all on, but in most cases I'm | interested only in one. Then typing errors or design flaws (like 'type | Synonym = Type', instead of wanted 'type Synonym a = Type a'; extended |

Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread Mark T.B. Carroll
apfelmus [EMAIL PROTECTED] writes: (snip) It's intentionally impossible. Frisby uses a dynamic programming approach that crucially depends on the fact that the grammar in question is context-free (actually something related, but the effect is the same). You're trying to parse a

[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
Mark T.B. Carroll wrote: apfelmus [EMAIL PROTECTED] writes: (snip) This not a correct Pascal program, nevertheless the parse succeeds just fine. The missing declaration for y will be detected when processing the abstract syntax tree further. The key point is that the shape of the abstract

Re: [Haskell-cafe] Re: Slower with ByteStrings?

2007-05-29 Thread Mirko Rahn
[fixed some typos, mainly missing primes] superset xs = superset' x . sort where x = sort xs _ `superset'` [] = True [] `superset'` _ = False (x:xs) `superset'` (y:ys) | x == y= xs `superset'` ys | x y= xs `superset'` (y:ys)

Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 apfelmus wrote: Mark T.B. Carroll wrote: I've been playing with Text.Parsers.Frisby to see how it stacks against other options and, while it's been great so far, I am finding that I can't encode a grammar where what's acceptable depends on what's

Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Simon Peyton-Jones wrote: | I wish the compilers would allow more fine grained switches on languages | extensions. -fglasgow-exts switches them all on, but in most cases I'm | interested only in one. Then typing errors or design flaws (like 'type

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Roberto Zunino
(re-joining the list -- I forgot to reply all) Vincent Kraeutler wrote: Roberto Zunino wrote: Vincent Kraeutler wrote: i see that the definition of fix (from Control.Monad.Fix) could not be any simpler: fix f = let x = f x in x I actually consider fix f = f (fix f) to be simpler. Alas,

Re: [Haskell-cafe] New book: Real-World Haskell!

2007-05-29 Thread Bryan O'Sullivan
Jules Bean wrote: No offense to the darcs creators, but 1) Only current Haskellers use it; everyone else either uses Subversion or is migrating to it; If that is true, then they have missed the point. DVC is a real win for most workflows. We are indeed using darcs, so this discussion is a

Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Ian Lynagh
On Tue, May 29, 2007 at 12:41:19PM -0400, Isaac Dupree wrote: Simon Peyton-Jones wrote: | I wish the compilers would allow more fine grained switches on languages | extensions. -fglasgow-exts switches them all on, but in most cases I'm | interested only in one. Then typing errors or design

Re: [Haskell-cafe] shared oneShot IO (was top-level state proposals)

2007-05-29 Thread Dan Weston
I was wondering why, since IO is an instance of MonadFix [1], and therefore of ArrowLoop (Kleisli m), and since The loop operator expresses computations in which an output value is fed back as input, even though the computation occurs only once. [2], the MonadFix or ArrowLoop class (through

Re: [Haskell-cafe] Darcs users [was: New book: Real-World Haskell!]

2007-05-29 Thread Doug Kirk
I didn't say there weren't others, simply that I didn't know of any others (I don't just go looking for things online all the time...having a real job really gets in the way of these things)! So I wasn't really trying to disparage darcs. But here's another statistic:

Re: [Haskell-cafe] New book: Real-World Haskell!

2007-05-29 Thread Doug Kirk
OTOH, I work for companies, and they really value their assets, especially software assets. So they *want* centralized stuff, so they can ensure they have consistent backups (in the U.S.A. there is a lot of regulation under Sarbanes-Oxley that requires this stuff). Right now we're using

Re: [Haskell-cafe] Language extensions [was: Memoization]

2007-05-29 Thread Andrew Coppin
Claus Reinke wrote: I'm thinking more about things like phantom types, rank-N polymorphism, functional dependencies, GADTs, etc etc etc that nobody actually understands. this seems to be overly polymorphic in generalising over all types of Haskell programmers, rather than admitting the

Re: [Haskell-cafe] Mysterious monads

2007-05-29 Thread Andrew Coppin
Nicolas Frisby wrote: Your intended behavior for Reader indicates stateful computational features. The read later roughly expands to be read by some monadic action on the rhs of a = as in (read = \x - read {-this is later-} = ...) Recognizing the stateful nature gives you two options: 1)

Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin
Tomasz Zielonka wrote: On Mon, May 28, 2007 at 11:43:47AM +0100, Andrew Coppin wrote: - Chapter 2 is... puzzling. Personally I've never seen the point of trying to check a program against a specification. If you find a mismatch then which thing is wrong - the program, or the spec?

Re: [Haskell-cafe] data PLZ a

2007-05-29 Thread Andrew Coppin
Donald Bruce Stewart wrote: We got the names wrong! data PLZ a = AWSUM_THX a | O_NOES String instance Monad PLZ where return= AWSUM_THX fail = O_NOES O_NOES s= _ = O_NOES s AWSUM_THX x = f = f x Thanks to mauke on #haskell.

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Andrew Coppin
Vincent Kraeutler wrote: Donald Bruce Stewart wrote: P.S. Have some cute code: Control.Monad.Fix.fix ((1:) . scanl (+) 1) this is cute indeed! (do you keep an emergency reserve of those around for situations like this? ;-)) LOL! I bet he does as well... I don't know. I

Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin
Henning Thielemann wrote: On Sun, 27 May 2007, Andrew Coppin wrote: Personally, I try to avoid ever using list comprehensions. Me too. Successfully, I have to add. But every now and then I discover an expression which is apparently not expressible without them - which is odd,

Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Tim Chevalier
On 5/29/07, Andrew Coppin [EMAIL PROTECTED] wrote: My point is for most programs, trying to figure out exactly what you want the program to do is going to be much harder than implementing a program that does it. Writing a spec can help with figuring out what you want your program to do.

Re: [Haskell-cafe] Cute code

2007-05-29 Thread Andrew Coppin
Donald Bruce Stewart wrote: I use it when I need a local loop expression, maybe once every couple of months. A real world example from xmonad, f = fix $ \again - do more - checkMaskEvent d enterWindowMask ev when more again That is, keep sucking up X events till

Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Andrew Coppin
Tim Chevalier wrote: On 5/29/07, Andrew Coppin [EMAIL PROTECTED] wrote: My point is for most programs, trying to figure out exactly what you want the program to do is going to be much harder than implementing a program that does it. Writing a spec can help with figuring out what you want your

[Haskell-cafe] Re: Language extensions

2007-05-29 Thread Jon Fairbairn
Andrew Coppin [EMAIL PROTECTED] writes: OTOH, how many function can you write with :: [Int] - Int? Quite a lot, but if you'd asked how many functions can you write :: Integer - Integer, the answer would be all of them (think about it). -- Jón Fairbairn [EMAIL

Re: [Haskell-cafe] Cute code [was: The C Equiv of != in Haskell miscommunication thread]

2007-05-29 Thread Albert Y. C. Lai
Vincent Kraeutler wrote: Donald Bruce Stewart wrote: P.S. Have some cute code: Control.Monad.Fix.fix ((1:) . scanl (+) 1) either way, if one of the Masters Of The Shadow Y Style on this list feels like throwing in another koan or two, you'll have at least one thankful audience member

[Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread apfelmus
Isaac Dupree wrote: apfelmus wrote: Mark T.B. Carroll wrote: I've been playing with Text.Parsers.Frisby to see how it stacks against other options and, while it's been great so far, I am finding that I can't encode a grammar where what's acceptable depends on what's already been parsed in

Re: [Haskell-cafe] shared oneShot IO (was top-level state proposals)

2007-05-29 Thread Claus Reinke
I was wondering why, since IO is an instance of MonadFix [1], and therefore of ArrowLoop (Kleisli m), and since The loop operator expresses computations in which an output value is fed back as input, even though the computation occurs only once. [2], the MonadFix or ArrowLoop class (through

Re: [Haskell-cafe] Control.Monad.State.Strict, mdo and let

2007-05-29 Thread Albert Y. C. Lai
Gracjan Polak wrote: Hi, I stumbled at some interaction of Control.Monad.State.Strict, mdo and let I do not understand. The following program: {-# OPTIONS_GHC -fglasgow-exts #-} module Main where import Control.Monad.State.Strict thenumber :: Float thenumber = flip execState 1.3 $ mdo c

Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread Isaac Dupree
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 apfelmus wrote: Isaac Dupree wrote: apfelmus wrote: Mark T.B. Carroll wrote: I've been playing with Text.Parsers.Frisby to see how it stacks against other options and, while it's been great so far, I am finding that I can't encode a grammar

[Haskell-cafe] teaming up for the IFCP contest

2007-05-29 Thread Tim Docker
I've put aside the weekend of July 20-23 for the ICFP contest (http:// www.icfpcontest.org/), and am looking to form or join a haskell wielding team. Any interest? Geographically I'm in Sydney, but have entered in a previous year with a team of 3 from around the globe which worked fine.

Re: [Haskell-cafe] Re: Frisby grammars that have context

2007-05-29 Thread Robin Green
On Tue, 29 May 2007 19:28:02 -0400 Isaac Dupree [EMAIL PROTECTED] wrote: Luckily, Haskell's laziness means that doing an extra postprocessing pass doesn't necessarily yield two traversals requiring the whole file to be stored in memory, nor worse hacks. (For grammars that aren't too wild /

Re: [Haskell-cafe] Help with terminal IO

2007-05-29 Thread Jason Dagit
On 5/27/07, Ryan Ingram [EMAIL PROTECTED] wrote: I was hoping that hSetBuffering would turn off the line buffering for stdin, but it doesn't seem to work. module Main where import System.IO main :: IO () main = do hSetBuffering stdin NoBuffering hSetBuffering stdout NoBuffering

Re: [Haskell-cafe] The C Equiv of != in Haskell miscommunication thread

2007-05-29 Thread Jason Dagit
On 5/28/07, Donald Bruce Stewart [EMAIL PROTECTED] wrote: This thread should end, guys. It is inappropriate for the Haskell lists, and appears to have been a simple misunderstanding anyway. Thanks everyone. Please stay friendly! -- Don P.S. Have some cute code: Control.Monad.Fix.fix

Re: [Haskell-cafe] New book: Real-World Haskell!

2007-05-29 Thread Jason Dagit
On 5/29/07, Doug Kirk [EMAIL PROTECTED] wrote: OTOH, I work for companies, and they really value their assets, especially software assets. So they *want* centralized stuff, so they can ensure they have consistent backups (in the U.S.A. there is a lot of regulation under Sarbanes-Oxley that

[Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p
Hello, Can anyone give me some tips concerning the following error: myPrompt ghc --make -fffi f.hs -l mylib.lib ghc --make -fffi f.hs -l mylib.lib [1 of 1] Compiling Main ( f.hs, f.o ) Linking f.exe ... d:\ghc\ghc6.6\gcc-lib\ld.exe: cannot find -l-Ld:/ghc/ghc6.6

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Brandon S. Allbery KF8NH
On May 29, 2007, at 23:01 , jeff p wrote: myPrompt ghc --make -fffi f.hs -l mylib.lib For historical reasons, you can't have a space between the -l and the library name. It's inserting an empty library name into the link command, which is producing the odd cannot find error. --

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p
Hello, On 5/29/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: On May 29, 2007, at 23:01 , jeff p wrote: myPrompt ghc --make -fffi f.hs -l mylib.lib For historical reasons, you can't have a space between the -l and the library name. It's inserting an empty library name into the

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Brandon S. Allbery KF8NH
On May 29, 2007, at 23:09 , jeff p wrote: d:\ghc\ghc6.6\gcc-lib\ld.exe: cannot find -lmylib.lib collect2: ld returned 1 exit status which is strange because the file mylib.lib is in the same directory as the haskell code. Typically -l appends the necessary extension itself (.lib on

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Stefan O'Rear
On Tue, May 29, 2007 at 11:09:15PM -0400, jeff p wrote: Hello, On 5/29/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: On May 29, 2007, at 23:01 , jeff p wrote: myPrompt ghc --make -fffi f.hs -l mylib.lib For historical reasons, you can't have a space between the -l and the

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Stefan O'Rear
On Tue, May 29, 2007 at 11:12:14PM -0400, Brandon S. Allbery KF8NH wrote: It may be easier to see if ghc has an option to pass through the next argument straight to the linker, or even recognizes .lib files and -Wl,foobar Stefan ___ Haskell-Cafe

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p
Hello, Thanks for the tips. I've gotten to the point where linking fails on an undefined reference. The strange thing about this is that when I make a C program to call the library function and compile with: myPrompt gcc f.c mylib.lib everything works fine. I think ghc is using it's own

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Stefan O'Rear
On Tue, May 29, 2007 at 11:48:18PM -0400, jeff p wrote: Hello, Thanks for the tips. I've gotten to the point where linking fails on an undefined reference. The strange thing about this is that when I make a C program to call the library function and compile with: myPrompt gcc f.c

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread jeff p
Hello, No, but ghc does pass a lot of funny flags... Double check ccall v. stdcall in the import declaration. That bites a lot of people on Windows. My import statement originally looked like: foreign import ccall mylib.h myFun my_fun :: CDouble - IO (Ptr CDouble) and my original

Re: [Haskell-cafe] Language extensions

2007-05-29 Thread Stefan Holdermans
True in principle. But if writing the spec is harder than writing the actual program, all it means is you spend longer trying to figure out how to express intuitively simple concepts using advanced and very abstract and subtle predicate calculus. As it turns out, Haskell sometimes makes a

Re: [Haskell-cafe] ffi linking problem

2007-05-29 Thread Stefan O'Rear
On Wed, May 30, 2007 at 12:28:43AM -0400, jeff p wrote: Hello, No, but ghc does pass a lot of funny flags... Double check ccall v. stdcall in the import declaration. That bites a lot of people on Windows. My import statement originally looked like: foreign import ccall mylib.h

Re: [Haskell-cafe] Darcs users [was: New book: Real-World Haskell!]

2007-05-29 Thread Ketil Malde
On Tue, 2007-05-29 at 14:05 -0500, Doug Kirk wrote: I *want* people (and companies) to move to Haskell; therefore, I want to lower the entry price. The goal is to introduce a new language, not a new SCM tool. You certainly wouldn't want to leave the impression that one MUST use darcs in order