Re: [Haskell-cafe] out of core computing in haskell

2007-08-13 Thread Stefan O'Rear
On Mon, Aug 13, 2007 at 12:29:25PM -0700, Carter T Schonwald wrote: Hello Everyone, I'm not quite sure if I'm posing this question correctly, but what facilities currently exist in haskell to nicely deal with datastructures that won't fit within a given machine's ram? And if there are no

Re: [Haskell-cafe] Syntax for lambda case proposal could be \of

2007-08-15 Thread Stefan O'Rear
On Wed, Aug 15, 2007 at 06:58:40PM +0100, Duncan Coutts wrote: On Wed, 2007-08-15 at 10:50 -0700, Stefan O'Rear wrote: OTOH, your proposal provides (IMO) much more natural syntax for multi-pattern anonymous functions, especially if we stipulate that unlike a case (but like a lambda) you

[Haskell-cafe] Re: trouble building 6.7 on ubuntu

2007-08-16 Thread Stefan O'Rear
On Thu, Aug 16, 2007 at 01:01:12PM -0400, Thomas Hartman wrote: I repeated the install attempt described below using darcs head, including the extra libs. I got the exact same error as before. Setup: Warning: Unknown fields: nhc98-options (line 173) and then a cryptic error

Re: [Haskell-cafe] trouble building regex-base 0.91 on ghc 6.7

2007-08-17 Thread Stefan O'Rear
On Fri, Aug 17, 2007 at 02:40:33PM -0400, Thomas Hartman wrote: I'm trying to build the latest regex base, which is required for the other regex packages under ghc 6.7 It complains that it can't find Data.Sequence, because it's in a hidden module containers. I added containers to the cabal

Re: [Haskell-cafe] trouble compiling import GHC.Prim(MutableByteArray#, ..... (building regex-tdfa from darcs) -- what's that # sign doing?

2007-08-17 Thread Stefan O'Rear
On Fri, Aug 17, 2007 at 04:27:29PM -0400, Thomas Hartman wrote: trying to compile regex-tdfa, I ran into another issue. (earlier I had a cabal problem but that's resolved.) there's a line that won't compile, neither for ghc 6.6.1 nor 6.7 import

Re: [Haskell-cafe] trouble compiling import GHC.Prim(MutableByteArray#, ..... (building regex-tdfa from darcs) -- what's that # sign doing?

2007-08-17 Thread Stefan O'Rear
On Fri, Aug 17, 2007 at 08:13:55PM -0400, Thomas Hartman wrote: Thanks Stefan. I got regex tdfa to compile on 6.7. FWIW, here's a patch, generated with darcs whatsnew against a fresh unzip of regex tdfa 0.92 I didn't patch against the darcs head because this uses a language progma in {-#

Re: [Haskell-cafe] GHC optimisations

2007-08-19 Thread Stefan O'Rear
On Sun, Aug 19, 2007 at 12:53:07PM +0100, Andrew Coppin wrote: Does GHC do stuff like converting (2*) into (shift 1) or converting x + x into 2*x? For a good time, compile some code which uses even or odd :: Int - Bool using -O2 -fasm -ddump-asm... The compiler *really* shouldn't be using

Re: [Haskell-cafe] Re: trouble compiling import GHC.Prim(MutableByteArray#, ..... (building regex-tdfa from darcs) -- what's that # sign doing?

2007-08-19 Thread Stefan O'Rear
On Sun, Aug 19, 2007 at 11:25:49PM +0100, ChrisK wrote: #ifdef __GLASGOW_HASKELL__ foreign import ccall unsafe memcpy memcpy :: MutableByteArray# RealWorld - MutableByteArray# RealWorld - Int# - IO () {-# INLINE copySTU #-} copySTU :: (Show i,Ix i,MArray (STUArray s) e (ST s))

Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 05:27:04AM -0700, Ryan Ingram wrote: I have a C function of type void f ( HsWord32* p0, HsWord32* p1, HsWord32 size ); along with the FFI declaration: foreign import ccall unsafe f :: Ptr Word32 - Ptr Word32 - Word32 - IO () In my Haskell code I have an

Re: [Haskell-cafe] Newbie question: Where is StackOverflow on the Wiki?

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 11:21:01AM -0500, Lanny Ripple wrote: Not really more efficient but plays to the language implementation's strengths. Imagine take 10 $ foo (10^9) and take 10 $ bar (10^9) bar wouldn't evaluate until the 10^9 was done. (And I just ground my laptop to a

Re: [Haskell-cafe] GHC optimisations

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 06:30:27PM +0100, Andrew Coppin wrote: Stefan O'Rear wrote: On Sun, Aug 19, 2007 at 12:53:07PM +0100, Andrew Coppin wrote: Does GHC do stuff like converting (2*) into (shift 1) or converting x + x into 2*x? For a good time, compile some code which uses even

Re: [Haskell-cafe] Tying the knot with unknown keys

2007-08-20 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 03:39:28PM -0700, Dan Piponi wrote: On 8/20/07, David Ritchie MacIver [EMAIL PROTECTED] wrote: I was playing with some code for compiling regular expressions to finite state machines and I ran into the following problem. I've met exactly the same problem myself and

Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 11:03:45PM -0700, Ryan Ingram wrote: Thanks to everyone, especially Bulat Ziganshin. In http://haskell.org/haskellwiki/Modern_array_libraries there is enough information to do what I want. It specifically mentions that it's OK to pass ByteArray# and

Re: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Stefan O'Rear
On Mon, Aug 20, 2007 at 11:47:06PM -0700, Ryan Ingram wrote: Your code is broken in a most evil and insidious way. Interesting. This is for a toy project, so I'm not too worried, but lets say I wanted to do this correctly and I was set on using IOUArray for some reason. Heh, I'm a lot

Re: Re[2]: [Haskell-cafe] How can I pass IOUArrays to FFI functions?

2007-08-21 Thread Stefan O'Rear
On Tue, Aug 21, 2007 at 12:50:22AM -0700, Ryan Ingram wrote: Ah, sneaky. That code is fine because it uses unsafeCoerce# on memcpy, changing memcpy from whatever type it is, into MutableByteArray# s# - MutableByteArray# s# - Int# - s# - (# s#, () #) So as long as the GC understands

Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Stefan O'Rear
On Tue, Aug 21, 2007 at 01:14:20PM +0100, Rodrigo Queiro wrote: On my system, the C version runs about 9x faster than the haskell version (with -O3 and -O2 -fvia-c -optc-O3 respectively). However, GCC seems to produce about 70 lines of assembly for the main loop, compared to about 10 from GHC.

Re: [Haskell-cafe] GHC optimisations

2007-08-21 Thread Stefan O'Rear
On Tue, Aug 21, 2007 at 09:39:32PM +0800, Hugh Perkins wrote: On 8/21/07, Stefan O'Rear [EMAIL PROTECTED] wrote: Currently, it's never worse. GHC's backend is about as good as GCC; most of the optimiations it doesn't do are not possible for GCC because of various lack-of-information

Re: [Haskell-cafe] GHC optimisations

2007-08-22 Thread Stefan O'Rear
On Wed, Aug 22, 2007 at 09:04:11AM +0100, Simon Peyton-Jones wrote: | First of all, optimizing mod and div can not be done with PrelRules, | because they are not primitives, quot and rem are. Yes, you can do them with PrelRules! Check out PrelRules.builtinRules. | Multiplication and

Re: [Haskell-cafe] GHC optimisations

2007-08-22 Thread Stefan O'Rear
On Wed, Aug 22, 2007 at 06:36:15PM +0100, Neil Mitchell wrote: Hi If Num obeys ring axioms, fromInteger is a perfectly fine ring-homomorphism. (It's also the first or second homomorphism taught.) Does Int obey these axioms? I'm thinking that assuming properties about things such as

Re: [Haskell-cafe] Tackling IO (the correct way)

2007-08-22 Thread Stefan O'Rear
On Thu, Aug 23, 2007 at 06:04:54AM +0100, Dave Tapley wrote: ... Now I wish to update a HOpenGL window synchronously with this. To establish this I make a new HOpenGL window return an IORef (IO ()) which holds the actions to draw my graphics. In this fashion: ... Because neither 'mapM_

Re: [Haskell-cafe] Dynamic thread management?

2007-08-22 Thread Stefan O'Rear
On Thu, Aug 23, 2007 at 06:27:43AM +0100, Hugh Perkins wrote: On 8/22/07, Brandon Michael Moore [EMAIL PROTECTED] wrote: Automatic threading is inherently limited by data dependencies. You can't run a function that branches on an argument in parallel with the computation producing that

Re: [Haskell-cafe] newbie - how to call a Haskell interpreter from C

2007-08-25 Thread Stefan O'Rear
On Sat, Aug 25, 2007 at 12:34:45PM -0400, Brock Peabody wrote: On 8/25/07, Henk-Jan van Tuyl [EMAIL PROTECTED] wrote: The easiest way to run Haskell software from a C program is to give the shell command: runhaskell Foo.hs I'm a newbie but not that new :) I really have to be

Re: [Haskell-cafe] Ideas

2007-08-25 Thread Stefan O'Rear
On Sat, Aug 25, 2007 at 07:43:30PM +0100, Andrew Coppin wrote: Neil Mitchell wrote: HI Flippi (google: Haskell Flippi) ...and yet haskell.org uses WikiMedia? (Which is written in something bizzare like Perl...) Yes, but WikiMedia is a result of years of work, Flippi is a

Re: [Haskell-cafe] Re: Parsec is being weird at me

2007-08-25 Thread Stefan O'Rear
On Sat, Aug 25, 2007 at 08:18:29PM +0100, Andrew Coppin wrote: But hang on a minute... many parses 0 or more occurrances of an item. sepBy parses 0 or more occurrances of an item, seperated by another item. endBy parses 0 or more occurrances of an item, terminated by another item.

Re: [Haskell-cafe] GHC from source makes a great hardware test

2007-08-25 Thread Stefan O'Rear
On Sat, Aug 25, 2007 at 09:33:25PM -0700, Dave Bayer wrote: I recently did the classic push a shopping cart down the aisle at Fry's to build a Core 2 Quad computer, with Linux swap and a soft raid array spread across three 750 GB sata hard disks. I had some potential first build issues,

Re: [Haskell-cafe] Geometry

2007-08-26 Thread Stefan O'Rear
On Mon, Aug 27, 2007 at 11:04:58AM +1000, Tony Morris wrote: -BEGIN PGP SIGNED MESSAGE- Hash: SHA1 I went camping on the weekend and a friend of mine who is a builder asked me many questions on geometry as they apply to his every day work - - most of which I could answer.

Re: [Haskell-cafe] GHC 6.6.1 and SELinux issues

2007-08-29 Thread Stefan O'Rear
On Wed, Aug 29, 2007 at 10:40:41PM +0400, Alexander Vodomerov wrote: On Wed, Aug 29, 2007 at 08:41:12AM -0700, Bryan O'Sullivan wrote: The underlying problem is harder to fix: the default SELinux policy doesn't allow PROT_EXEC pages to be mapped with PROT_WRITE, for obvious reasons.

Re: [Haskell-cafe] Learn Prolog...

2007-09-04 Thread Stefan O'Rear
On Wed, Sep 05, 2007 at 01:21:52PM +1000, Thomas Conway wrote: but to interpret this as a *program* you have to consider how it will be executed. In particular, using SLD resolution, conjunction (/\, or ',' in Prolog notation) is not commutative as it is in predicate logic. I've always

Re: [Haskell-cafe] About mplus

2007-09-04 Thread Stefan O'Rear
On Wed, Sep 05, 2007 at 03:35:03PM +1200, ok wrote: I've been thinking about making a data type an instance of MonadPlus. From the Haddock documentation at haskell.org, I see that any such instance should satisfy mzero `mplus` x = x x `mplus` mzero = x mzero = f =

Re: [Haskell-cafe] Typeclasses and implicit parameters

2007-09-06 Thread Stefan O'Rear
On Thu, Sep 06, 2007 at 06:49:21AM -0400, [EMAIL PROTECTED] wrote: For completeness, here's the final solution, courtesy of int-e (whose real name I don't know; sorry), which is much more elegant than I Bertram Felgenhauer bindString :: (forall s. StringAsType s = Mark s a) - String - a

Re: [Haskell-cafe] Re: turning an imperative loop to Haskell

2007-09-06 Thread Stefan O'Rear
On Thu, Sep 06, 2007 at 03:42:50PM +0200, apfelmus wrote: Dougal Stanton wrote: To create an infinite list where each f(u) depends on the previous u, with a single seed value, use 'iterate': main = mapM_ (uncurry (printf %d %f\n)) (zip [1..50] (iterate f 3)) How about main = sequence_ $

Re: [Haskell-cafe] Elevator pitch for Haskell.

2007-09-08 Thread Stefan O'Rear
On Sat, Sep 08, 2007 at 05:44:47PM +0100, Neil Mitchell wrote: I'd like to think that Haskell will soon be ready for prime-time. But let's face it, the language is 20 years old already... Most of your problems are lack of libraries. We've had Cabal in mainstream for maybe a year, hackage

Re: [Haskell-cafe] Re: getting crazy with character encoding

2007-09-12 Thread Stefan O'Rear
On Thu, Sep 13, 2007 at 12:23:33AM +, Aaron Denney wrote: Unfortunately, at this point it is a well entrenched bug, and changing the behaviour will undoubtedly break programs. ... There should be another system for getting the exact bytes in and out (as Word8s, say, rather than Chars), and

Re: [Haskell-cafe] Re: getting crazy with character encoding

2007-09-13 Thread Stefan O'Rear
On Thu, Sep 13, 2007 at 12:06:15PM +0200, Ketil Malde wrote: On Wed, 2007-09-12 at 17:40 -0700, Stefan O'Rear wrote: On Thu, Sep 13, 2007 at 12:23:33AM +, Aaron Denney wrote: Unfortunately, at this point it is a well entrenched bug, and changing the behaviour will undoubtedly break

Re: [Haskell-cafe] Monad.Reader 8: Haskell, the new C++

2007-09-13 Thread Stefan O'Rear
On Fri, Sep 14, 2007 at 11:05:34AM +1000, Manuel M T Chakravarty wrote: Just to complete transferring the discussion from the ephemeral hpaste to the mailing list. My response to the lack of being able to display normalised types was that GHC actually goes to considerable trouble to

Re: [Haskell-cafe] Data.Binary Endianness

2007-09-15 Thread Stefan O'Rear
On Sat, Sep 15, 2007 at 01:20:57PM +0200, Sven Panne wrote: On Tuesday 11 September 2007 09:17, Don Stewart wrote: Just in case people didn't see, the `binary' package lives on http://darcs.haskell.org/binary/ However, Lennart Kolmodin, Duncan and I are actively maintaining and

Re: [Haskell-cafe] How can I stop GHCi from calling show for IO actions?

2007-09-15 Thread Stefan O'Rear
On Sat, Sep 15, 2007 at 08:35:02PM -0700, Ryan Ingram wrote: Prelude let inf = repeat 1 Prelude inf [1,1,(lots of output until I press ctrl-c),Interrupted. (I expect this to happen) Prelude let x = inf (no output here!) Prelude :t x x :: [Integer] Prelude return inf [1,1,(lots of output

Re: [Haskell-cafe] unknown RTS option: -N2

2007-09-15 Thread Stefan O'Rear
On Sat, Sep 15, 2007 at 09:49:56PM -0700, Gregory Propf wrote: I've built a program with the -threaded option using ghc. This option is supposed to link your program to the threaded runtime with support for multicore CPUS (mine is a dual core). The program pukes with the message in the

Re: [Haskell-cafe] GHC 6.7 on Windows / containers-0.1 package?

2007-09-19 Thread Stefan O'Rear
On Wed, Sep 19, 2007 at 10:24:24PM +0100, Neil Mitchell wrote: Hi Peter, So I grabbed ghc-6.7.20070824 (=the latest one for Windows I could find) and the extra-libs, compiled and installed the GLUT package (which I needed), but when I compile my library, I get Could not find

Re: [Haskell-cafe] length defined with foldr

2007-09-19 Thread Stefan O'Rear
On Thu, Sep 20, 2007 at 04:17:54AM +0100, PR Stanley wrote: Hi length = foldr (. n . 1 + n) 0 Any idea how to define length with foldr. The above definition doesn't make much sense. Many thanks, Paul length = foldr (λ_ n → 1 + n) 0 or, in ASCII concrete syntax length = foldr (\_ n - 1 +

Re: [Haskell-cafe] Haskell guards

2007-09-20 Thread Stefan O'Rear
On Thu, Sep 20, 2007 at 05:20:46PM +0400, Victor Nazarov wrote: I still can't remember how guards are treated in Haskell. Here is the code snippet in question: foo a | a == 1 = 6 foo a | a == 2 = 7 foo a = 8 Would Haskell fall through to the third alternative if a is not equal to 1 or

Re: [Haskell-cafe] Accumulator value for and and or

2007-09-20 Thread Stefan O'Rear
On Fri, Sep 21, 2007 at 03:48:25AM +0100, PR Stanley wrote: Hi or = foldl (||) False and = foldl () True I can understand the rationale for the accumulator value - True [] where [] = True and True || [] where [] = False Other than the practical convenience is there a reason for having the

Re: [Haskell-cafe] GHC 6.7 on Windows / containers-0.1 package?

2007-09-21 Thread Stefan O'Rear
On Fri, Sep 21, 2007 at 05:40:59PM -0300, Felipe Almeida Lessa wrote: On 9/21/07, Peter Verswyvelen [EMAIL PROTECTED] wrote: Since I'm used to write heavily multi-threaded/multi-core code in imperative languages, I would like to understand more about the existing execution models, and

Re: [Haskell-cafe] what is f=f (not) doing ?

2007-09-22 Thread Stefan O'Rear
On Sat, Sep 22, 2007 at 12:58:12PM +0200, Peter Verswyvelen wrote: Peter Verswyvelen wrote: http://www.haskell.org/ghc/docs/2.10/users_guide/user_146.html http://www.haskell.org/ghc/docs/2.10/users_guide/user_146.htmlseems to confirm that? Oops, sorry, these seems to be docs for

Re: [Haskell-cafe] Composition Operator

2007-09-24 Thread Stefan O'Rear
On Mon, Sep 24, 2007 at 06:47:05PM -0700, Dan Weston wrote: Of course I should have proofread this one more time! What is a point? A point in Hask* is a type with only a single value in it, from which all other values can be constructed. Every value x maps trivially into a function (const

Re: [Haskell-cafe] Packages and how to load them

2007-09-27 Thread Stefan O'Rear
On Thu, Sep 27, 2007 at 06:10:37PM -0400, bbrown wrote: If I have a set of haskell code and I create a directory with the source that has the following imports. (some_dir/MyLib.hs) module MyLib where And then I want to use that set of code at the top level directory, eg: MyTest.hs

Re: [Haskell-cafe] Rewriting Char.ord

2007-09-29 Thread Stefan O'Rear
On Sat, Sep 29, 2007 at 03:11:20PM +0100, PR Stanley wrote: Hi ord :: Char - Int ord c = sum [1 | x - ['\0'..'\255'], x c] Any comments? Any alternatives? Cheers, Paul It's waay slow, it breaks for characters 255. ord :: Char - Int ord = fromEnum As Char is an instance of 'Enum'. If you

Re: [Haskell-cafe] Order of Declaration

2007-09-29 Thread Stefan O'Rear
On Sat, Sep 29, 2007 at 12:05:01PM -0500, Derek Elkins wrote: On Sat, 2007-09-29 at 17:58 +0100, PR Stanley wrote: Hi in C type languages a function must be declared before its application. Would I be right in thinking that this isn't the case in Functional languages? For example:

Re: [Haskell-cafe] Compiling Simple Regex Program

2007-09-29 Thread Stefan O'Rear
On Sat, Sep 29, 2007 at 09:25:40PM -0400, Andrew Trusty wrote: Hello, I'm using GHC 6.6.1 under Windows XP and I can't get the following simple program to compile. import Text.Regex main = putStrLn (subRegex (mkRegex c) abc a) It runs in GHCi just fine but GHC gives the following output

Re: [Haskell-cafe] The kind of (-)

2007-09-30 Thread Stefan O'Rear
On Mon, Oct 01, 2007 at 11:40:20AM +1000, jeeva suresh wrote: Hi Guys! According ghci the kind of (-) is ?? - ? - * What do the '??' mean? What is the difference between the '?' and the '*' It's an implementation detail leaking out. GHC uses a set of special types to represent primitive

Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-02 Thread Stefan O'Rear
On Tue, Oct 02, 2007 at 08:02:30AM -0700, Deborah Goldsmith wrote: UTF-16 is the type used in all the APIs. Everything else is considered an encoding conversion. CoreFoundation uses UTF-16 internally except when the string fits entirely in a single-byte legacy encoding like MacRoman or

Re: [Haskell-cafe] Parsing R5RS Scheme with Parsec

2007-10-02 Thread Stefan O'Rear
On Tue, Oct 02, 2007 at 11:36:52AM -0300, Alex Queiroz wrote: Hallo, On 10/2/07, Brandon S. Allbery KF8NH [EMAIL PROTECTED] wrote: On Oct 2, 2007, at 9:52 , Alex Queiroz wrote: (parseDottedList ls) | (parseProperList ls) I've factored out the common left sub-expression in

Re: [Haskell-cafe] Re: PROPOSAL: New efficient Unicode string library.

2007-10-02 Thread Stefan O'Rear
On Tue, Oct 02, 2007 at 11:05:38PM +0200, Johan Tibell wrote: I do not believe that anyone was seriously advocating multiple blessed encodings. The main question is *which* encoding to bless. 99+% of text I encounter is in US-ASCII, so I would favor UTF-8. Why is UTF-16 better for me?

Re: [Haskell-cafe] bizarre memory usage with data.binary

2007-10-02 Thread Stefan O'Rear
On Wed, Oct 03, 2007 at 01:22:25AM +0200, Roel van Dijk wrote: Does it terminate? Looks like you are summing all the natural numbers. On a turing machine it should run forever, on a real computer it should run out of memory. Unless I am missing something obvious :-) There are only about 4

Re: [Haskell-cafe] bizarre memory usage with data.binary

2007-10-02 Thread Stefan O'Rear
On Tue, Oct 02, 2007 at 04:08:01PM -0700, Anatoly Yakovenko wrote: i am getting some weird memory usage out of this program: module Main where import Data.Binary import Data.List(foldl') main = do let sum' = foldl' (+) 0 let list::[Int] = decode $ encode $ ([1..] :: [Int])

Re: [Haskell-cafe] Haskell FFI and finalizers

2007-10-03 Thread Stefan O'Rear
On Wed, Oct 03, 2007 at 05:57:58PM +0200, Maxime Henrion wrote: I have recently developed a small set of bindings for a C library, and encountered a problem that I think could be interesting to others. My problem was that the C function I was writing bindings to expects to be passed a FILE

Re: [Haskell-cafe] Haskell FFI and finalizers

2007-10-03 Thread Stefan O'Rear
On Thu, Oct 04, 2007 at 12:55:41AM +0200, Maxime Henrion wrote: When writing the binding for foo_new(), I need to open a file with fopen() to pass it the FILE *. Then I get a struct foo * that I can easily associate the the foo_destroy() finalizer. However, when finalizing the struct foo *

Re: [Haskell-cafe] gtk2hs in Ubuntu Gutsy

2007-10-04 Thread Stefan O'Rear
On Thu, Oct 04, 2007 at 09:31:56AM -0700, Chad Scherrer wrote: I just installed the beta release for Ubuntu Gutsy, and I noticed that gtk2hs (provided by libghc6-gtk-dev) is still at version 0.9.10.5-1ubuntu1. Worse, it's apparently not installable; when I try I get this message:

[Haskell-cafe] Re: [Haskell] reading from stdin

2007-10-04 Thread Stefan O'Rear
On Thu, Oct 04, 2007 at 05:46:09PM +0100, Axel Simon wrote: Hi, I'm trying to continuously output data to a file handle while reading single characters from the user to adjust the speed at which things are output. I'm interested to get this to work in Hugs on Windows. I successfully used

Re: [Haskell-cafe] New slogan for haskell.org

2007-10-04 Thread Stefan O'Rear
On Thu, Oct 04, 2007 at 10:36:40AM -0700, Don Stewart wrote: The Haskell website has the rather strange motivational text: Haskell is a general purpose, purely functional programming language featuring static typing, higher order functions, polymorphism, type classes, and monadic

Re: [Haskell-cafe] ANNOUNCE: binary 0.4: high performance, pure binary parsing and serialisation

2007-10-06 Thread Stefan O'Rear
On Sat, Oct 06, 2007 at 10:16:37PM +0100, Andrew Coppin wrote: Don Stewart wrote: *Very* high performance can be expected, with throughput over 1G/sec observed in practice (good enough for most networking scenarios, we suspect). Um... I wasn't aware that there was any harddrive or

Re: [Haskell-cafe] symbol type?

2007-10-10 Thread Stefan O'Rear
On Tue, Oct 09, 2007 at 11:28:08PM -0700, Michael Vanier wrote: Is there an implementation of a symbol type in Haskell i.e. a string which has a constant-time comparison operation? Yes, I beleive GHC uses one (utils/FastString.lhs iirs) Stefan signature.asc Description: Digital signature

Re: [Haskell-cafe] How to thoroughly clean up Haskell stuff on linux

2007-10-12 Thread Stefan O'Rear
On Fri, Oct 12, 2007 at 07:31:45PM -0400, Brandon S. Allbery KF8NH wrote: I don't think haddock has to depend on lamdbabot. But I saw Skipping HaddockHoogle during the build. Isn't the Hoogle thing related to Lambdabot? Or they are unrelated. Only insofar has Lambdabot has an interface to

Re: [Haskell-cafe] Performance problem with random numbers

2007-10-12 Thread Stefan O'Rear
On Sat, Oct 13, 2007 at 12:09:57AM +0200, ntupel wrote: Dear all, I have implemented a small module to generate random items with a given probability distribution using the alias approach [1] and unfortunately compared to similar implementations in C++ or Java it is about 10 times slower. I

Re: [Haskell-cafe] Re: [Haskell] Re: Trying to install binary-0.4

2007-10-15 Thread Stefan O'Rear
On Mon, Oct 15, 2007 at 10:57:48PM +0100, Claus Reinke wrote: so i wonder why everyone else claims to be happy with the status quo? We aren't happy with the status quo. Rather, we know that no matter how much we do, the situation will never improve, so most of us have stopped wasting out time.

Re: [Haskell-cafe] Re: Proposal: register a package as providing several API versions

2007-10-16 Thread Stefan O'Rear
On Tue, Oct 16, 2007 at 01:57:01PM +0100, Simon Marlow wrote: Certainly, this is something we want to support. However, there's an important difference between shared-library linking and Haskell: in Haskell, a superset of an API is not backwards-compatible, because it has the potential to

Re: [Haskell-cafe] Performance problem with random numbers

2007-10-16 Thread Stefan O'Rear
On Tue, Oct 16, 2007 at 06:07:39PM +0200, Peter Verswyvelen wrote: Does the GHC code generator makes use of SIMD instructions? Maybe via the C compiler? No. GHC uses GCC extensions, and GCC doesn't support automatic SIMD use. (You could use -unreg and an advanced compiler. Good luck finding

Re: [Haskell-cafe] Re: Bug in runInteractiveProcess?

2007-10-17 Thread Stefan O'Rear
On Wed, Oct 17, 2007 at 08:46:41AM -0700, Donn Cave wrote: On Wed, 17 Oct 2007, Simon Marlow wrote: ... Note that forkProcess doesn't currently work with +RTS -N2 (or any value larger than 1), and it isn't likely to in the future. I suspect forkProcess should be deprecated. The

Re: [Haskell-cafe] Tutorial: Curry-Howard Correspondence

2007-10-17 Thread Stefan O'Rear
On Wed, Oct 17, 2007 at 03:06:33PM -0700, Dan Weston wrote: 2) the function must halt for all defined arguments fix :: forall p . (p - p) - p fix f = let x = f x in x consider: foo :: ((a - a) - a) - a foo x = x id foo is a valid proof of a true theorem, but does not halt for the defined

Re: [Haskell-cafe] Tutorial: Curry-Howard Correspondence

2007-10-17 Thread Stefan O'Rear
On Wed, Oct 17, 2007 at 06:45:04PM -0700, Dan Weston wrote: _|_ does not provide a witness to a theorem in any consistent logic (otherwise everything could be proved from it), yet it inhabits every type in Haskell. If the only invalid type instance is _|_, then a necessary and sufficient

Re: [Haskell-cafe] Do you trust Wikipedia?

2007-10-17 Thread Stefan O'Rear
On Thu, Oct 18, 2007 at 02:31:10AM +0100, PR Stanley wrote: Hi Do you trust mathematical materials on Wikipedia? Paul Yes, unless they look like they were written by a crackpot. It's kinda hard to introduce errors when any sufficiently unobvious fact is accompanied by a proof sketch. Stefan

Re: [Haskell-cafe] Tutorial: Curry-Howard Correspondence

2007-10-17 Thread Stefan O'Rear
inhabits SN[a - b], and TERM2 inhabits SN[a], then (TERM1) (TERM2) inhabits SN[b]. No mention of evaluation required. Is it clear now? Stefan Stefan O'Rear wrote: On Wed, Oct 17, 2007 at 03:06:33PM -0700, Dan Weston wrote: 2) the function must halt for all defined arguments fix

Re: [Haskell-cafe] Re: [Haskell] Announce: generating free theorems, online and offline

2007-10-18 Thread Stefan O'Rear
On Thu, Oct 18, 2007 at 03:36:01AM -0400, [EMAIL PROTECTED] wrote: (As an aside: The H98 report still list the right-zero law as being a law for MonadPlus, even though most MonadPlus instances don't obey it. That's actually a defect in the report.) All the MonadPlus I can think of

Re: [Haskell-cafe] Do you trust Wikipedia?

2007-10-18 Thread Stefan O'Rear
On Fri, Oct 19, 2007 at 03:06:21AM +0200, [EMAIL PROTECTED] wrote: Stefan O'Rear writes: ... Latex page sources are infinitely superior to unadorned images of unknown providence. Of course, most certainly! But I failed to understand the relation to Wikipedia. OK, I see. If you look

Re: [Haskell-cafe] Re: [Haskell] Announce: generating free theorems, online and offline

2007-10-18 Thread Stefan O'Rear
On Thu, Oct 18, 2007 at 08:39:04PM -0400, David Menendez wrote: On 10/18/07, Stefan O'Rear [EMAIL PROTECTED] wrote: On Thu, Oct 18, 2007 at 03:36:01AM -0400, [EMAIL PROTECTED] wrote: (As an aside: The H98 report still list the right-zero law as being a law for MonadPlus, even though most

Re: [Haskell-cafe] Do you trust Wikipedia?

2007-10-18 Thread Stefan O'Rear
On Fri, Oct 19, 2007 at 02:45:45AM +0200, [EMAIL PROTECTED] wrote: PR Stanley writes: One of the reasons I'm interested in Wikipedia and Wikibook is because you're more likely to find Latex source code used for typesetting the maths. Latex is the one and only 100% tool right now. A lot of

Re: [Haskell-cafe] Transformation sequence

2007-10-20 Thread Stefan O'Rear
On Sat, Oct 20, 2007 at 08:05:37PM +0100, Andrew Coppin wrote: Brent Yorgey wrote: Hmm... I'm having trouble understanding exactly what you want. In particular, I don't understand what this statement: But what I *really* want is to print out the transformation *sequence*. has to do with

Re: [Haskell-cafe] Re: How much of Haskell was possible 20 years ago?

2007-10-21 Thread Stefan O'Rear
On Sun, Oct 21, 2007 at 10:02:25PM -0400, Brandon S. Allbery KF8NH wrote: On Oct 21, 2007, at 21:31 , Maurí cio wrote: Anyway, what I would like would be a theoretical answer. Is there something fundamentally diferent between a C compiler and a Haskell one that makes the former fits into 30Kb

Re: [Haskell-cafe] ANN: Math.OEIS 0.1

2007-10-22 Thread Stefan O'Rear
On Mon, Oct 22, 2007 at 07:20:47AM -0400, Brent Yorgey wrote: * returning a lazy infinite list for infinite sequences via an embedded general AI and Mathematica interpreter. Assuming you have a licensed copy of Mathematica, get in touch with Cale Gibbard; he has done all the work for

Re: [Haskell-cafe] Binary constants in Haskell

2007-10-25 Thread Stefan O'Rear
On Thu, Oct 25, 2007 at 02:40:36PM +0200, Josef Svenningsson wrote: On 10/24/07, Neil Mitchell [EMAIL PROTECTED] wrote: Hi Are there binary constants in Haskell, as we have, for instance, 0o232 for octal and 0xD29A for hexadecimal? No, though it is an interesting idea.

Re: [Haskell-cafe] Binary constants in Haskell

2007-10-25 Thread Stefan O'Rear
On Thu, Oct 25, 2007 at 09:41:27PM +0200, Henning Thielemann wrote: Total functions, full laziness, and compile time evaluation of finite non-bottom CAFs... If I write a program that approximates a big but fixed number of digits of Pi - how can we prevent the compiler from computing Pi,

Re: [Haskell-cafe] newbie optimization question

2007-10-28 Thread Stefan O'Rear
On Sun, Oct 28, 2007 at 11:26:46AM -0400, Prabhakar Ragde wrote: Jerzy Karczmarczuk wrote: Just a trivial comment... 1. Don't speak about comparing *languages* when you compare *algorithms*, and in particular data structures. 2. Please, DO code the above in C, using linked lists. Compare

Re: [Haskell-cafe] newbie optimization question

2007-10-28 Thread Stefan O'Rear
On Sun, Oct 28, 2007 at 08:40:28PM +0100, Daniel Fischer wrote: Am Sonntag, 28. Oktober 2007 20:09 schrieb Derek Elkins: snip That fits with my experience writing low level numeric code -- Integer can be a killer. Inline machine operations v. out-of-line calls to an arbitrary

Re: [Haskell-cafe] Fusion for fun and profi (Was: newbie optimization question)

2007-10-28 Thread Stefan O'Rear
On Sun, Oct 28, 2007 at 01:25:19PM -0700, Don Stewart wrote: Finally, we can manually translate the C code into a confusing set of nested loops with interleaved IO, main = loop 1 where loop !i | i 1 = return () | otherwise = if i == go i 0 1 then

Re: [Haskell-cafe] Fusion for fun and profi (Was: newbie optimization question)

2007-10-28 Thread Stefan O'Rear
On Sun, Oct 28, 2007 at 01:43:07PM -0700, Don Stewart wrote: stefanor: IO blocks unboxing in GHC. How fast is your mock-C code refactored to do IO outside of the loops only? It doesn't! The above code yields: Main.$wloop :: GHC.Prim.Int# - GHC.Prim.State#

Re: [Haskell-cafe] Newbie Question on Setting the GHC Search Path

2007-10-29 Thread Stefan O'Rear
On Mon, Oct 29, 2007 at 04:25:45AM -0700, Benjamin L. Russell wrote: One factor that is slightly unusual about this phenomenon is that it only occurs with GHC, but not with Hugs 98. Typing :cd D:\From C Drive\Documents and Settings\DekuDekuplex\Programming Practice\Haskell\GHC Are you

Re: [Haskell-cafe] Re: [Haskell] Image manipulation

2007-10-29 Thread Stefan O'Rear
On Mon, Oct 29, 2007 at 02:39:58PM -0700, Tim Chevalier wrote: [redirecting to haskell-cafe] On 10/29/07, Brent Yorgey [EMAIL PROTECTED] wrote: Haskell is a wonderful language, so I hate to say this...but personally I don't see the benefit of using Haskell here, unless the manipulations you

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-10-31 Thread Stefan O'Rear
On Wed, Oct 31, 2007 at 03:37:12PM +, Neil Mitchell wrote: Hi I've been working on optimising Haskell for a little while (http://www-users.cs.york.ac.uk/~ndm/supero/), so here are my thoughts on this. The Clean and Haskell languages both reduce to pretty much the same Core language,

Re: [Haskell-cafe] Re: Why can't Haskell be faster?

2007-10-31 Thread Stefan O'Rear
On Thu, Nov 01, 2007 at 02:30:17AM +, Neil Mitchell wrote: Hi I don't think the register allocater is being rewritten so much as it is being written: From talking to Ben, who rewrote the register allocator over the summer, he said that the new graph based register allocator is

Re: [Haskell-cafe] Memory-mapped arrays? (IArray interfaces, slices, and so on)

2007-11-07 Thread Stefan O'Rear
On Wed, Nov 07, 2007 at 10:10:16PM +, Jules Bean wrote: Joel Reymont wrote: Is there such a thing as memory-mapped arrays in GHC? In principle, there could be an IArray instance to memory-mapped files. (There could also be a mutable version, but just the IArray version would be

Re: [Haskell-cafe] [OT] GHC uninstall on Linux

2007-11-07 Thread Stefan O'Rear
On Wed, Nov 07, 2007 at 10:41:53AM +0100, Dusan Kolar wrote: Hello all, I use tar.bz2 binary distribution of GHC compiler as my distro does not use any supported packaging system. Everything is fine, but... I want to install the new version of the GHC compiler. Is there any (easy) way, how

Re: [Haskell-cafe] Haskell performance question

2007-11-08 Thread Stefan O'Rear
On Fri, Nov 09, 2007 at 01:39:55AM +0100, Thomas Schilling wrote: On Thu, 2007-11-08 at 16:24 -0800, Stefan O'Rear wrote: On Thu, Nov 08, 2007 at 07:57:23PM +0100, Thomas Schilling wrote: $ ghc --make -O2 ghc-bench.hs Even for GCC (/not/ G_H_C)? No, GCC implements -Ox properly. I

Re: [Haskell-cafe] Haskell performance question

2007-11-08 Thread Stefan O'Rear
On Thu, Nov 08, 2007 at 05:03:54PM -0800, Stefan O'Rear wrote: On Fri, Nov 09, 2007 at 01:39:55AM +0100, Thomas Schilling wrote: On Thu, 2007-11-08 at 16:24 -0800, Stefan O'Rear wrote: On Thu, Nov 08, 2007 at 07:57:23PM +0100, Thomas Schilling wrote: $ ghc --make -O2 ghc-bench.hs

Re: [Haskell-cafe] Haskell performance question

2007-11-08 Thread Stefan O'Rear
On Thu, Nov 08, 2007 at 07:57:23PM +0100, Thomas Schilling wrote: $ ghc --make -O2 ghc-bench.hs and got: $ time ./ghc-bench 2.0e7 real0m0.714s user0m0.576s sys 0m0.132s $ time ./ghcbC 2000.00 real0m0.305s user0m0.164s sys 0m0.132s This

Re: [Haskell-cafe] MD5? (was: Haskell performance question)

2007-11-08 Thread Stefan O'Rear
On Thu, Nov 08, 2007 at 06:14:20PM -0500, Thomas M. DuBuisson wrote: Glad you asked! http://sequence.complete.org/node/367 I just posted that last night! Once I get a a community.haskell.org login I will put the code on darcs. The short of it it: 1) The code is still ugly, I haven't

Re: [Haskell-cafe] MD5?

2007-11-09 Thread Stefan O'Rear
On Fri, Nov 09, 2007 at 09:05:58PM +, Andrew Coppin wrote: The MD5SUM.EXE file I have chokes if you ask it to hash a file in another directory. It will hash from stdin, or from a file in the current directory, but point-blank refuses to hash anything else. So I'd have to write my

Re: [Haskell-cafe] Building Haskell stuff on Windows

2007-11-09 Thread Stefan O'Rear
On Fri, Nov 09, 2007 at 07:38:28PM +, Andrew Coppin wrote: ...there's a libraries list? (And a Cabal list??) http://haskell.org/mailman/listinfo/ Stefan signature.asc Description: Digital signature ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Trouble using unboxed arrays

2007-11-10 Thread Stefan O'Rear
On Sat, Nov 10, 2007 at 11:09:54AM -0800, Justin Bailey wrote: I would like to create a data structure that uses an unboxed array as one of its components. I would like the data structure to be parameterized over the type of the elements of the array. Further, I'd like to build the array using

Re: [Haskell-cafe] Somewhat random history question - chicken and egg

2007-11-11 Thread Stefan O'Rear
On Sun, Nov 11, 2007 at 11:07:29AM +, Neil Mitchell wrote: Hi ...if GHC is written in Haskell, how the heck did they compile GHC in the first place? GHC was not the first Haskell compiler, hbc was the main compiler at some point, so I suspect they used hbc. There was also lazy ML

Re: [Haskell-cafe] Performance help

2007-11-13 Thread Stefan O'Rear
On Tue, Nov 13, 2007 at 02:45:33PM -0800, Justin Bailey wrote: On Nov 13, 2007 2:21 PM, Ryan Ingram [EMAIL PROTECTED] wrote: Never mind, I realized this is a ring buffer with `mod` s. That's another slow operation when you're doing code as tight as this. If you can guarantee the ring is

  1   2   3   4   5   >