Re: [Haskell-cafe] interrupting an accept()ing thread

2007-07-06 Thread Lukas Mai
Am Freitag, 6. Juli 2007 04:15 schrieb Thomas Conway: On 7/6/07, Lukas Mai [EMAIL PROTECTED] wrote: I don't see how this solves the problem. AFAICS acceptLoop never returns and sok is never closed. On the other hand, my program doesn't need a liveOpCount because the subthreads take care of

Re[2]: [Haskell-cafe] A very nontrivial parser

2007-07-06 Thread Bulat Ziganshin
Hello Andrew, Thursday, July 5, 2007, 11:45:14 PM, you wrote: Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?) MPTCs and ATs look useful.

[Haskell-cafe] RE: Modern Haskell books (was Re: A very nontrivial parser)

2007-07-06 Thread peterv
but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new Haskell' standard The

[Haskell-cafe] Re[2]: Modern Haskell books (was Re: A very nontrivial parser)

2007-07-06 Thread Bulat Ziganshin
Hello peterv, The problem I face is that most (all?) Haskell books I could find deal with Haskell 98... Are there any books out that cover the modern Haskell extensions? chapter 7 of ghc manual, *old* hugs manual, and hundreds of papers on haskell site :) -- Best regards, Bulat

Re: [Haskell-cafe] RE: Modern Haskell books (was Re: A very nontrivial parser)

2007-07-06 Thread Donald Bruce Stewart
bf3: but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new Haskell'

Re: [Haskell-cafe] RE: Modern Haskell books (was Re: A very nontrivial parser)

2007-07-06 Thread Donald Bruce Stewart
dons: bf3: but afair you don't yet have too much experience even with H98 language? from my POV, H98 as is useful for learning, but not for real apps. there is wide common subset of GHC and Hugs language extensions and this set (with exception for FD) will probably become new

Re[2]: [Haskell-cafe] RE: Modern Haskell books (was Re: A very nontrivial parser)

2007-07-06 Thread Bulat Ziganshin
Hello peterv, Friday, July 6, 2007, 2:03:24 PM, you wrote: For example, for the brand new F# language I bought the book http://www.amazon.com/Foundations-F-Robert-Pickering/dp/1590597575 which covers almost everything you need to create real-world applications, from GUIs to databases to 2D/3D

[Haskell-cafe] Combinators for Bi-Directional Tree Transformations: A Linguistic Approach to the View Update Problem in Haskell

2007-07-06 Thread Pasqualino 'Titto' Assini
Hi, I wondered if anyone had written an Haskell implementation of the combinators described in: Combinators for Bi-Directional Tree Transformations: A Linguistic Approach to the View Update Problem (see the Papers section of http://www.seas.upenn.edu/~harmony/). Harmony's source is in O'Caml

Re: [Haskell-cafe] A very nontrivial parser [Source code]

2007-07-06 Thread Claus Reinke
source code is always useful, as it is concrete. but some comments about purpose and important aspects would help, too, lest we optimise away the parts you're most interested in. as it stands, i must assume that 'decodeRLEb' is the purpose of the exercise, and it isn't clear to me why that

Re: [Haskell-cafe] reimplementing break (incorrectly) quickcheck p list gives me feedback that it breaks on list, but not what predicate test caused the breakage

2007-07-06 Thread Ketil Malde
On Thu, 2007-07-05 at 19:37 -0400, Thomas Hartman wrote: I am a total quickcheck noob. Is there a way to find out what predicate test function is, below? testMyBreak= quickCheck $ \p l - myBreak p (l :: [Int]) == break p l Well - you could try naming the qc property? I.e.

Re: Re[2]: [Haskell-cafe] Binary serialization, was Re: Abstraction leak

2007-07-06 Thread Ketil Malde
On Thu, 2007-07-05 at 18:08 +0100, Duncan Coutts wrote: - Found that on hackage, downloaded and built OK. Lots of scary warnings about happy, greencard etc, not being found during configure, but let's go on. I've complained about these before, although I don't think anyone

[Haskell-cafe] Nix for Hackage/Cabal

2007-07-06 Thread apfelmus
Hello, http://nix.cs.uu.nl/index.html Nix is a purely functional package manager. This means that it treats packages like values in purely functional programming languages such as Haskell - they are built by functions that don't have side-effects, and they never change after they have been

[Haskell-cafe] Problem using ap -- No instance for (Monad ((-) [[a]]))

2007-07-06 Thread Jim Burton
If I try a function to make a point-free version of the function in this fold -- foldr (\x ys - ys ++ map (x:) ys) [[]] :pl gives me GOA Control.Monad :pl (\x ys - ys ++ map (x:) ys) ap (++) . map . (:) GOA Control.Monad :t ap (++) . map . (:) ap (++) . map . (:) :: (Monad ((-) [[a]])) = a

Re: [Haskell-cafe] reimplementing break (incorrectly) quickcheck p list gives me feedback that it breaks on list, but not what predicate test caused the breakage

2007-07-06 Thread Josef Svenningsson
On 7/6/07, Thomas Hartman [EMAIL PROTECTED] wrote: I am a total quickcheck noob. Is there a way to find out what predicate test function is, below? The trick that I know of to do that is to not generate a function in the first place, but a data type which can represent various functions of

[Haskell-cafe] Class Interfaces in OOHaskell?

2007-07-06 Thread Scott West
Hello all, Looking at the OOHaskell black (grey?) magic, and wondering if there would be an interesting way to construct class interfaces using the OOHaskell paradigm? I'm trying to do it as so (assume relevant types/proxies declared): type FigureInter = Record ( Draw :=: IO ()

Re: [Haskell-cafe] update on SoC projects?

2007-07-06 Thread Claus Reinke
there still seem to be only three entries for status reports (of 9 projects) on that page. have the other projects been abandoned? since the existing reports are fairly terse, it isn't always easy to guess what is going on (eg, why would parts of hackage web depend on things like debian, sdl,

Re: [Haskell-cafe] Problem using ap -- No instance for (Monad ((-) [[a]]))

2007-07-06 Thread Bulat Ziganshin
Hello Jim, Friday, July 6, 2007, 7:12:27 PM, you wrote: No instance for (Monad ((-) [[a]])) :l Control.Monad.Instances -- Best regards, Bulatmailto:[EMAIL PROTECTED] ___ Haskell-Cafe mailing list

[Haskell-cafe] Branches of a binary tree

2007-07-06 Thread Kyle L Bittinger
I am writing some code to find peaks in molecular spectra. I represent a spectrum as a list of numbers (intensities) and build a binary search tree of the positions in the list (x-values) sorted by intensity. Peaks in the spectrum appear as branches of the tree. My task is to return branches

Re: [Haskell-cafe] Branches of a binary tree

2007-07-06 Thread Stefan O'Rear
On Fri, Jul 06, 2007 at 11:47:58AM -0400, Kyle L Bittinger wrote: I am writing some code to find peaks in molecular spectra. I represent a spectrum as a list of numbers (intensities) and build a binary search tree of the positions in the list (x-values) sorted by intensity. In general, the

Re: [Haskell-cafe] update on SoC projects?

2007-07-06 Thread Kenn Knowles
On Fri, Jul 06, 2007 at 04:30:36PM +0100, Claus Reinke wrote: there still seem to be only three entries for status reports (of 9 projects) on that page. have the other projects been abandoned? The updating of Hat hasn't been abandoned, and I just added an update. Sorry about the delay; I've

Re: [Haskell-cafe] Nix for Hackage/Cabal

2007-07-06 Thread Duncan Coutts
On Fri, 2007-07-06 at 16:47 +0200, apfelmus wrote: Hello, http://nix.cs.uu.nl/index.html Nix is a purely functional package manager. This means that it treats packages like values in purely functional programming languages such as Haskell - they are built by functions that don't have

[Haskell-cafe] Re: Nix for Hackage/Cabal

2007-07-06 Thread apfelmus
Duncan Coutts wrote: On Fri, 2007-07-06 at 16:47 +0200, apfelmus wrote: http://nix.cs.uu.nl/index.html I was under the impression that it didn't work on Windows. From another quick look at the website, it looks like that's right. Does anybody happen to know otherwise? I have no idea,

Re: Re[2]: [Haskell-cafe] Binary serialization, was Re: Abstraction leak

2007-07-06 Thread Duncan Coutts
On Fri, 2007-07-06 at 08:26 +0200, Ketil Malde wrote: On Thu, 2007-07-05 at 18:08 +0100, Duncan Coutts wrote: - Found that on hackage, downloaded and built OK. Lots of scary warnings about happy, greencard etc, not being found during configure, but let's go on. I've complained

Re: [Haskell-cafe] Re: Nix for Hackage/Cabal

2007-07-06 Thread Esa Ilari Vuokko
On 7/6/07, apfelmus [EMAIL PROTECTED] wrote: Duncan Coutts wrote: On Fri, 2007-07-06 at 16:47 +0200, apfelmus wrote: http://nix.cs.uu.nl/index.html I was under the impression that it didn't work on Windows. From another quick look at the website, it looks like that's right. Does anybody

Re: [Haskell-cafe] A very nontrivial parser

2007-07-06 Thread Andrew Coppin
Donald Bruce Stewart wrote: andrewcoppin: Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?) Some cover edge cases, some are just

Re: [Haskell-cafe] A very nontrivial parser

2007-07-06 Thread Andrew Coppin
Claus Reinke wrote: source code is always useful, as it is concrete. but some comments about purpose and important aspects would help, too, lest we optimise away the parts you're most interested in. as it stands, i must assume that 'decodeRLEb' is the purpose of the exercise, and it isn't clear

Re: [Haskell-cafe] Re: Nix for Hackage/Cabal

2007-07-06 Thread Andreas Marth
If that means I have to have cygwin installed to use the installation tools thats not only a show stopper, but against the direction ghc took in the past to become independend of cygwin. - Original Message - From: apfelmus [EMAIL PROTECTED] To: haskell-cafe@haskell.org Sent: Friday, July

Re: [Haskell-cafe] A very nontrivial parser

2007-07-06 Thread Jonathan Cast
On Friday 06 July 2007, Andrew Coppin wrote: Stefan O'Rear wrote: How about . in module names? Now I'm almost *certain* that's now officially in the language... ;-) Nope. Never made it past candidate status (or version 0.0, for that matter). http://www.haskell.org/hierarchical-modules/

Re: [Haskell-cafe] Re: Nix for Hackage/Cabal

2007-07-06 Thread Bulat Ziganshin
Hello apfelmus, Friday, July 6, 2007, 8:19:58 PM, you wrote: I was under the impression that it didn't work on Windows. From another - Added support for Cygwin (Windows, i686-cygwin), Mac OS X on Intel cygwin isn't windows, it's backdoors : -- Best regards, Bulat

Re: [Haskell-cafe] A very nontrivial parser

2007-07-06 Thread Jonathan Cast
On Friday 06 July 2007, Andrew Coppin wrote: Donald Bruce Stewart wrote: andrewcoppin: Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?)

Re: [Haskell-cafe] A very nontrivial parser

2007-07-06 Thread Andrew Coppin
Stefan O'Rear wrote: How about . in module names? Now I'm almost *certain* that's now officially in the language... ;-) ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] needsaname :: ([a] - Maybe (b, [a])) - (b - [a]) - [a] - [a]

2007-07-06 Thread Bulat Ziganshin
Hello Jules, Friday, July 6, 2007, 10:00:12 PM, you wrote: to think of many more uses of this function. I actually wrote it to do HTML fix-up, working with the TagSoup library. A few quick definitions and it becomes easy to express things like 'remove all FONT, BR and U tags; replace all

Re: [Haskell-cafe] Nix for Hackage/Cabal

2007-07-06 Thread Arthur van Leeuwen
On 6-jul-2007, at 18:08, Duncan Coutts wrote: On Fri, 2007-07-06 at 16:47 +0200, apfelmus wrote: Hello, http://nix.cs.uu.nl/index.html Nix is a purely functional package manager. This means that it treats packages like values in purely functional programming languages such as Haskell

[Haskell-cafe] needsaname :: ([a] - Maybe (b, [a])) - (b - [a]) - [a] - [a]

2007-07-06 Thread Jules Bean
Hi, Yet another Function looking for a name post. Here's the type: morph :: ([a] - Maybe (b,[a])) - (b - [a]) - [a] - [a] Here, I am calling ([a] - Maybe (b,[a])) the 'selector'. It is actually the same type as a simple parser. I am calling (b - [a]) the 'transformer'. Once you've chosen

[Haskell-cafe] Re: Combinators for Bi-Directional Tree Transformations: A Linguistic Approach to the View Update Problem in Haskell

2007-07-06 Thread Benjamin Pierce
Hi Titto, I'm not aware of any Haskell implementations of these bi-directional combinators, but the core definitions are not very big -- someone looking at the ML code should have no trouble recreating them in Haskell. The main issue to take care of, beyond the mathematical description

[Haskell-cafe] A very edgy language (was: A very nontrivial parser)

2007-07-06 Thread Albert Y. C. Lai
Andrew Coppin wrote: Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?) Haskell is an extremely rare edge case to begin with. Non-strict (most

Re: [Haskell-cafe] Two-continuation `monads' and MonadMinus [Re: Parsers are monadic?]

2007-07-06 Thread David Menendez
[EMAIL PROTECTED] writes: Called MonadMinus, it is capable of defining LogicT monad with the true logical negation as well as interleaving and committed choice. Our ICFP05 paper describes MonadMinus monad (actually, the transformer) and LogicT as well as their two implementations. I just

Re: [Haskell-cafe] Two-continuation `monads' and MonadMinus [Re: Parsers are monadic?]

2007-07-06 Thread David Menendez
David Menendez writes: [EMAIL PROTECTED] writes: Called MonadMinus, it is capable of defining LogicT monad with the true logical negation as well as interleaving and committed choice. Our ICFP05 paper describes MonadMinus monad (actually, the transformer) and LogicT as well as their

[Haskell-cafe] GHC threads and SMP

2007-07-06 Thread Paul L
I have two parallel algorithms that use the lightweight GHC thread and forkIO. I compile them using the -threaded (or -smp) option, and run both with +RTS -N2 -RTS command line option. QSort is able to make use of the dual cores on my laptop -- top shows that two threads show up and both CPUs

Re: [Haskell-cafe] Nix for Hackage/Cabal

2007-07-06 Thread Marc Weber
of Cabal's functionality like finding compilers and such. I was under the impression that it didn't work on Windows. From another quick look at the website, it looks like that's right. Does anybody happen to know otherwise? It actually does. I've managed to compile it. You have one major

Re: [Haskell-cafe] needsaname :: ([a] - Maybe (b, [a])) - (b - [a]) - [a] - [a]

2007-07-06 Thread Jules Bean
Bulat Ziganshin wrote: Hello Jules, Friday, July 6, 2007, 10:00:12 PM, you wrote: to think of many more uses of this function. I actually wrote it to do HTML fix-up, working with the TagSoup library. A few quick definitions and it becomes easy to express things like 'remove all FONT, BR and U

Re: [Haskell-cafe] needsaname :: ([a] - Maybe (b, [a])) - (b - [a]) - [a] - [a]

2007-07-06 Thread J. Garrett Morris
morph :: ([a] - Maybe (b,[a])) - (b - [a]) - [a] - [a] Any reason not to call it 'replace'? /g On 7/6/07, Jules Bean [EMAIL PROTECTED] wrote: Hi, Yet another Function looking for a name post. Here's the type: morph :: ([a] - Maybe (b,[a])) - (b - [a]) - [a] - [a] Here, I am calling

[Haskell-cafe] Re: Combinators for Bi-Directional Tree Transformations: A Linguistic Approach to the View Update Problem in Haskell

2007-07-06 Thread Pasqualino 'Titto' Assini
Hello Benjamin, many thanks for you answer. On Friday 06 July 2007 20:43:03 Benjamin Pierce wrote: Hi Titto, I'm not aware of any Haskell implementations of these bi-directional combinators, but the core definitions are not very big -- someone looking at the ML code should have no trouble

[Haskell-cafe] Re: Class Interfaces in OOHaskell?

2007-07-06 Thread Scott West
I conquered the below problem, but now I have another question: How can one have two interface-classes that reference each other? For example, type Inter1 = Record ( MkFoo :=: Inter2 - IO () :*: HNil ) type Inter2 = Record ( MkBar :: Inter1 - IO () :*: HNil ) Obviously this is cyclical,

[Haskell-cafe] Re: GHC threads and SMP

2007-07-06 Thread Paul L
replying to my own message... the behavior is only when -O is used during compilation, otherwise they both run on 2 cores but at a much lower (1/100) speed. On 7/6/07, Paul L [EMAIL PROTECTED] wrote: I have two parallel algorithms that use the lightweight GHC thread and forkIO. I compile them

Re: [Haskell-cafe] Re: Class Interfaces in OOHaskell?

2007-07-06 Thread Brandon Michael Moore
On Fri, Jul 06, 2007 at 06:11:42PM -0400, Scott West wrote: I conquered the below problem, but now I have another question: How can one have two interface-classes that reference each other? For example, type Inter1 = Record ( MkFoo :=: Inter2 - IO () :*: HNil ) type Inter2 = Record

[Haskell-cafe] Haddock doesn't work -- with Haddock

2007-07-06 Thread Michael T. Richter
I've been wrestling the last few days with putting Haddock documentation into my code. After a dead-simple library failed to generate anything meaningful, I gave up, turfed my copy of Haddock and downloaded the latest from the web site. (Haddock 0.8, it seems.) runhaskell Setup.lhs

Re: [Haskell-cafe] Haddock doesn't work -- with Haddock

2007-07-06 Thread Donald Bruce Stewart
ttmrichter: I've been wrestling the last few days with putting Haddock documentation into my code. After a dead-simple library failed to generate anything meaningful, I gave up, turfed my copy of Haddock and downloaded the latest from the web site. (Haddock 0.8, it seems.)

Re: [Haskell-cafe] Haddock doesn't work -- with Haddock

2007-07-06 Thread Stefan O'Rear
On Sat, Jul 07, 2007 at 09:11:55AM +0800, Michael T. Richter wrote: I've been wrestling the last few days with putting Haddock documentation into my code. After a dead-simple library failed to generate anything meaningful, I gave up, turfed my copy of Haddock and downloaded the latest from

Re: [Haskell-cafe] Haddock doesn't work -- with Haddock

2007-07-06 Thread Michael T. Richter
On Sat, 2007-07-07 at 11:17 +1000, Donald Bruce Stewart wrote: Check that the comment is not using one the chars invalid in H98/haddock. '/' is a common source of issues. I really hope that the Haddock source doesn't use invalid Haddock comments ;) -- Michael T. Richter [EMAIL

Re: [Haskell-cafe] Haddock doesn't work -- with Haddock

2007-07-06 Thread Michael T. Richter
On Fri, 2007-06-07 at 18:22 -0700, Stefan O'Rear wrote: You've just ran into Cabal bug #14, or maybe #102. http://hackage.haskell.org/trac/hackage/ticket/14 http://hackage.haskell.org/trac/hackage/ticket/102 It doesn't appear to be either of these. My own projects use no form of

Re: [Haskell-cafe] Haddock doesn't work -- with Haddock

2007-07-06 Thread Stefan O'Rear
On Sat, Jul 07, 2007 at 09:40:57AM +0800, Michael T. Richter wrote: On Fri, 2007-06-07 at 18:22 -0700, Stefan O'Rear wrote: You've just ran into Cabal bug #14, or maybe #102. http://hackage.haskell.org/trac/hackage/ticket/14 http://hackage.haskell.org/trac/hackage/ticket/102 It

[Haskell-cafe] ANN: functorm-1.0

2007-07-06 Thread Stefan O'Rear
This is the Data.FunctorM module from 6.6's base, deleted from HEAD still used by some projects (notably jhc); this package can be used for compatibility. Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/functorm-1.0 Tarball:

Re: [Haskell-cafe] Haddock doesn't work -- with Haddock

2007-07-06 Thread Michael T. Richter
On Fri, 2007-06-07 at 18:43 -0700, Stefan O'Rear wrote: It doesn't appear to be either of these. My own projects use no form of pre-processing and exhibit exactly the same problem: a parse error on first character of the line after the first Haddock comment. I don't know if the Haddock

Re: [Haskell-cafe] needsaname :: ([a] - Maybe (b, [a])) - (b - [a]) - [a] - [a]

2007-07-06 Thread Felipe Almeida Lessa
I've written it to run over lists, but it would not be difficult to make it run over ByteStrings instead, and exploit the 'no-copying' effect on the bits of the stream which were not modified, which would be very handy for programs processing large bytestrings. I wonder if there's a efficient

Re: [Haskell-cafe] needsaname :: ([a] - Maybe (b, [a])) - (b - [a]) - [a] - [a]

2007-07-06 Thread Donald Bruce Stewart
felipe.lessa: I've written it to run over lists, but it would not be difficult to make it run over ByteStrings instead, and exploit the 'no-copying' effect on the bits of the stream which were not modified, which would be very handy for programs processing large bytestrings. I wonder if

Re: [Haskell-cafe] A very edgy language (was: A very nontrivial parser)

2007-07-06 Thread Donald Bruce Stewart
trebla: Andrew Coppin wrote: Personally, I just try to avoid *all* language extensions - mainly because most of them are utterly incomprehensible. (But then, perhaps that's just because they all cover extremely rare edge cases?) Haskell is an extremely rare edge case to begin with.

Re: [Haskell-cafe] interrupting an accept()ing thread

2007-07-06 Thread Rich Neswold
On 7/5/07, Lukas Mai [EMAIL PROTECTED] wrote: Hello, cafe! I have the following code (paraphrased): ... forkIO spin ... spin = do (t, _) - accept s -- (*) forkIO $ dealWith t -- (**) spin My problem is that I want to stop spin from another thread. The obvious solution would be

[Haskell-cafe] ANN: functorm-1.0.1

2007-07-06 Thread Stefan O'Rear
This is an update to remove a spurious dependency on the unix package (thanks to Andrea Vezzosi for the quick spot). I had used the vty cabal file as a template but forgot to fix the depenencies. Hackage: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/functorm-1.0.1 Tarball:

Re: [Haskell-cafe] A very edgy language

2007-07-06 Thread Albert Y. C. Lai
Donald Bruce Stewart wrote: Give #haskell is a far larger community than: #lisp #erlang #scheme #ocaml As well as #java #javascript #ruby #lua #d #perl6 Maybe we need to reconsider where the (FP) mainstream is now? :-) I don't know. #math is larger

Re: [Haskell-cafe] A very edgy language

2007-07-06 Thread Donald Bruce Stewart
trebla: Donald Bruce Stewart wrote: Give #haskell is a far larger community than: #lisp #erlang #scheme #ocaml As well as #java #javascript #ruby #lua #d #perl6 Maybe we need to reconsider where the (FP) mainstream is now? :-) I

[Haskell-cafe] Trying to make a Typeable instance

2007-07-06 Thread Adrian Hey
Hello, I'm trying to make the type (ListGT map k a) an instance of Typeable, where map is kind (* - *). data ListGT map k a = Empt | BraF ![k] a !(map (ListGT map k a)) | BraE ![k] !(map (ListGT map k a)) I thought I'd cracked it with something like this.. instance (Typeable (map (ListGT

Re: [Haskell-cafe] A very edgy language

2007-07-06 Thread Bill Wood
On Sat, 2007-07-07 at 15:08 +1000, Donald Bruce Stewart wrote: . . . I don't know. #math is larger than #accounting. Is it because math is more mainstream than accounting? I bet it is because math is more math is more *interesting* than accounting? :-) If we gotta have a theory, I'll