Re: [Haskell-cafe] is proof by testing possible?

2009-11-10 Thread Conor McBride
On 10 Nov 2009, at 05:52, Curt Sampson wrote: On 2009-11-09 14:22 -0800 (Mon), muad wrote: Proof: True for n = 0, 1, 2, 3, 4 (check!), hence true for all n. QED. ... Actually, the test is that it's true for 0 through 4 is not sufficient for a proof; It's enough testing... you also

[Haskell-cafe] pattern match failure as control structure

2009-11-10 Thread Dan Mead
hey all, is there something special about pattern match exceptions? i'm attempting to catch pattern match failures to use as control for a production system. so i want to be able to do something like catch (head []) (\e - print that theres pattern fail! ) any suggestions?

[Haskell-cafe] Re: is proof by testing possible?

2009-11-10 Thread Heinrich Apfelmus
Conor McBride wrote: and you can calculate how much testing is enough by computing an upper bound on the polynomial degree of the expression. (The summation operator increments degree, the difference operator decreases it, like in calculus.) This is sometimes described as the reflective

[Haskell-cafe] filter using foldr point-free?

2009-11-10 Thread damodar kulkarni
Hi, We can define filter using foldr as under: filter1 p = foldr (\x xs - (if (p x) then (x:xs) else xs)) [] Can we define filter using foldr but in pointfree style? Thanks -DM ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

Re: [Haskell-cafe] filter using foldr point-free?

2009-11-10 Thread Svein Ove Aas
On Tue, Nov 10, 2009 at 12:47 PM, damodar kulkarni kdamodar2...@gmail.com wrote: Hi, We can define filter using foldr as under: filter1 p = foldr (\x xs - (if (p x) then (x:xs) else xs))  [] Can we define filter using foldr but in pointfree style? Pointfree code is (nearly) always possible,

[Haskell-cafe] Type-indexed expressions with fixpoint

2009-11-10 Thread oleg
Brent Yorgey wrote: This email is literate Haskell. I'm struggling to come up with the right way to add a fixpoint constructor to an expression language described by a type-indexed GADT (details below). but since Haskell doesn't have type-level lambdas, I don't see how to make that work.

Re: [Haskell-cafe] Help Haskell driving Medical Instruments

2009-11-10 Thread Philippos Apolinarius
Hi, Jason. I don't know how to mark the call unsafe. And I don't know what is a *Nix (perhaps unix?). I am running the main program on Windows.  Here is the compilation script: ghc -fglasgow-exts serial.c  %1.hs -L./ -ljapi --make erase *.hi erase *.o strip %1.exe BTW I figure out that passing

Re: [Haskell-cafe] is proof by testing possible?

2009-11-10 Thread Curt Sampson
On 2009-11-10 08:24 + (Tue), Conor McBride wrote: On 10 Nov 2009, at 05:52, Curt Sampson wrote: This is sometimes described as the reflective proof method: express problem in language capturing decidable fragment; hit with big stick. Well, that's pretty sweet. *And* you get to use a big

Re: [Haskell-cafe] Help Haskell driving Medical Instruments

2009-11-10 Thread Daniel Fischer
Am Dienstag 10 November 2009 14:01:33 schrieb Philippos Apolinarius: Hi, Jason. I don't know how to mark the call unsafe. And I don't know what is a *Nix (perhaps unix?). Unix or unix-derivate (linux, BSD, ...) I am running the main program on Windows. Then it might be necesary to let the

[Haskell-cafe] Sending patches to ghc related repositories

2009-11-10 Thread Maurí­cio CA
Hi, all, I just tried to send a patch to a ghc tool. I see in hackage that the maintainer e-mail is 'cvs-fpto...@haskell.org' (package is hsc2hs). I tried sending darcs patch to this e-mail, but it's refused as it's not on that server allowed e-mails table. The patch isn't really important,

[Haskell-cafe] Static Linking Problem

2009-11-10 Thread MightyByte
I am trying to statically compile a simple haskell program so I can use it on a Linux computer without haskell and it's associated libraries. Here is a small example program that illustrates my problem: module Main where import Network.Fancy main = do withDgram (IP 127.0.0.1 1234) (flip

Re: [Haskell-cafe] pattern match failure as control structure

2009-11-10 Thread Dan Mead
i think that may be too in depth. all i'm trying to do is catch a regular pattern match exception On Tue, Nov 10, 2009 at 5:50 AM, Roel van Dijk vandijk.r...@gmail.com wrote: Have a look at this recently uploaded package: http://hackage.haskell.org/package/first-class-patterns Examine the

[Haskell-cafe] Parsec - separating Parsing from Lexing

2009-11-10 Thread Fernando Henrique Sanches
Hello. I'm currently implementing a MicroJava compiler for a college assignment (the implemented language was defined, the implementation language was of free choice). I've sucessfully implemented the lexer using Parsec. It has the type String - Parser [MJVal], where MJVal are all the possible

Re: [Haskell-cafe] pattern match failure as control structure

2009-11-10 Thread Nicolas Pouillard
Excerpts from Dan Mead's message of Tue Nov 10 20:23:26 +0100 2009: i think that may be too in depth. all i'm trying to do is catch a regular pattern match exception On Tue, Nov 10, 2009 at 5:50 AM, Roel van Dijk vandijk.r...@gmail.com wrote: Have a look at this recently uploaded package:

Re: [Haskell-cafe] pattern match failure as control structure

2009-11-10 Thread Dan Mead
thanks, i've got it working i'll probably post the code when i'm done On Tue, Nov 10, 2009 at 3:01 PM, Nicolas Pouillard nicolas.pouill...@gmail.com wrote: Excerpts from Dan Mead's message of Tue Nov 10 20:23:26 +0100 2009: i think that may be too in depth. all i'm trying to do is catch a

Re: [Haskell-cafe] Parsec - separating Parsing from Lexing

2009-11-10 Thread Sean Leather
I've sucessfully implemented the lexer using Parsec. It has the type String - Parser [MJVal], where MJVal are all the possible tokens. Great! You're partway there. How should I implement the parser separated from the lexer? That is, how should I parse Tokens instead of Strings in the

Re: [Haskell-cafe] Help Haskell driving Medical Instruments

2009-11-10 Thread Jason Dusek
2009/11/10 Philippos Apolinarius phi50...@yahoo.ca I don't know how to mark the call unsafe. [...] I am running the main program on Windows. Marking it unsafe is done by putting unsafe in the foreign import declaration. Even if it turns out not to fix the problem, it reduces the overhead

[Haskell-cafe] (state) monad and CPS

2009-11-10 Thread jean-christophe mincke
Hello, I would like to get some advice about state monad (or any other monad I guess) and CPS. Let's take a simple exemple (see the code below) 'walk' is a function written in CPS that compute the number of nodes leaves in a tree. It use a counter which is explicitly passed through calls.

[Haskell-cafe] Calling all Haskellers in Huntsville, Alabama, or surrounding areas!

2009-11-10 Thread Jake McArthur
Shae Errisson, myself, Greg Bacon, and some other locals who I think might not have as big a presence online are starting a user's group in Huntsville, AL. Please join the Google group / mailing list [1] if you are interested! [1] http://groups.google.com/group/alabamahaskell - Jake McArthur

Re: [Haskell-cafe] Parsec - separating Parsing from Lexing

2009-11-10 Thread Jason Dusek
You have to bootstrap your parser with something that takes an `MJVal` and updates the parser state. Here is a simple example: http://github.com/jsnx/system-uuid/blob/master/Options.hs This is a parser for command line options. It parses a list of `String`s, not `Char`s (because

Re: [Haskell-cafe] (state) monad and CPS

2009-11-10 Thread Gregory Crosswhite
Yes; check out the module Control.Monad.Cont, which has a monad for continuation passing style. In particular, note that most of the monads in Control.Monad.* are stackable in that there is a version of the monad which you can stack on top of an existing monad. So for example, you could

[Haskell-cafe] ICFP 2010: Call for papers

2009-11-10 Thread Wouter Swierstra
= Call for Papers ICFP 2010: International Conference on Functional Programming Baltimore, Maryland, 27 -- 29 September 2010 http://www.icfpconference.org/icfp2010

Re: [Haskell-cafe] Static Linking Problem

2009-11-10 Thread Ketil Malde
MightyByte mightyb...@gmail.com writes: After a bit of googling, I came to the conclusion that I needed to compile it with ghc --make -static -optl-static Foo.hs. Using only -static or -optl-static by themselves did not generate a statically linked binary. But when I compile with both those

Re: [Haskell-cafe] Help to solve simple problem !

2009-11-10 Thread Ezra Lalonde
The following program should work: ===compress.hs= toList :: (Eq a) = [a] - [[a]] toList [] = [] toList x = start : toList end where (start, end) = span (==(head x)) x toTuple :: [a] - (a, Int) toTuple x = (head x, length x) compress :: Eq a = [a] - [(a, Int)] compress x =

[Haskell-cafe] Cabal HackORama -- how to handle par and pseq on stable platforms

2009-11-10 Thread John D. Ramsdell
I am writing a Cabal file for an application that uses par and pseq. I want to support both modern distributions of GHC and the version that comes with Ubuntu Hardy Heron, a Long Term Support version of Ubuntu that will be retired in April 2011. It provides GHC 6.8.2 with Cabal 1.2.3.0 and no

Re: [Haskell-cafe] Help to solve simple problem !

2009-11-10 Thread Eduard Sergeev
Aneto wrote: compress :: Eq a = [a] - [(a, Int)] If you have string AAABCCC it transforms it to : {A, 3} {B,1} {C,3} Basically you need to group equal elements of the list first and then transform every group (which is a list of equal elements) to the tuple of (first_element , the_

Re: [Haskell-cafe] help with Haskell performance

2009-11-10 Thread Gokul P. Nair
--- On Sat, 11/7/09, Don Stewart d...@galois.com wrote: General notes:   * unpack is almost always wrong.   * list indexing with !! is almost always wrong.   * words/lines are often wrong for parsing large files (they build large list structures).   * toList/fromList probably aren't the best

Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors

2009-11-10 Thread Daniel Gorín
On Sep 30, 2009, at 2:20 AM, Martin Hofmann wrote: Thanks a lot. You ought to be able to add a Control.Monad.CatchIO.catch clause to your interpreter to catch this kind of errors, if you want. I forgot to mention that this didn't work for me either. Thanks for the report! You are

Re: [Haskell-cafe] help with Haskell performance

2009-11-10 Thread Brad Larsen
On Tue, Nov 10, 2009 at 8:20 PM, Gokul P. Nair gpnai...@yahoo.com wrote: --- On Sat, 11/7/09, Don Stewart d...@galois.com wrote: General notes: * unpack is almost always wrong. * list indexing with !! is almost always wrong. * words/lines are often wrong for parsing large files

[Haskell-cafe] Opinion about JHC

2009-11-10 Thread Philippos Apolinarius
I discovered a Haskell compiler that generates very small and fast code. In fact, it beats Clean. It has the following properties: 1 --- One can cross-compile programs easily. For instance, here is how I generated code for Windows: jhc --cross -mwin32 genetic.hs -o genetic 2 -- It seems to be

Re: [Haskell-cafe] Opinion about JHC

2009-11-10 Thread Thomas DuBuisson
1 -- How active is the team who is writing the JHC compiler? The Team is John and Its not his day job afaik. Lemmih used to work on it before he forked it into LHC which has since evolved into a new (GRIN based) backend for GHC [1]. 2 -- Is it complete Haskell? The author claims that it is;

Re: [Haskell-cafe] (state) monad and CPS

2009-11-10 Thread Ryan Ingram
Something like this should work: newtype ContState r s a = ContState { runCS :: s - (a - s - r) - r } instance Monad (ContState r s) where return a = ContState $ \s k - k a s m = f = ContState $ \s0 k - runCS m s $ \a s1 - runCS (f a) s1 k instance MonadState s (ContState r s) where

Re: [Haskell-cafe] Problems with Language.Haskell.Interpreter and errors

2009-11-10 Thread Martin Hofmann
Although late, still very much appreciated. Thanks a lot! Cheers, Martin ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

[Haskell-cafe] Working with multiple projects

2009-11-10 Thread Tony Morris
I have two projects that I intend to put on hackage soon. One depends on the other. I have cabaled both. I am wondering how others work with this kind of set up where changes are made to both libraries as they work. -- Tony Morris http://tmorris.net/