Re: [Haskell-cafe] A question about monad laws

2008-03-14 Thread askyle
Wolfgang Jeltsch-2 wrote: No, I think, it’s the Prelude’s fault to define (==) as “floating point equality”. My bad, I meant IEEE (==) when I said it was our fault. I concur that the Prelude is at fault for using the (==) symbol for FP equality. Even if you don't demand from (==) to be an

Re: [Haskell-cafe] Ackermann Function Memoization, GHC Weird Output or Bug?

2008-03-14 Thread Eric Mertens
Smaller example of this behavior: array ((0,0),(1,1)) [((1,1),6)] ! (0,3) 6 -- Eric Mertens ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] A question about monad laws

2008-03-14 Thread askyle
ajb-2 wrote: Define: f = g = \x - f x = g So you're either not taking (=) as primitive or you're stating the additional property that there exists (=) such that f = g === (= g) . f (from which you can easily show that (f . g) = h === (f = h) . g ). A presentation of the monad laws

Re: [Haskell-cafe] A question about monad laws

2008-03-14 Thread ajb
G'day all. Quoting askyle [EMAIL PROTECTED]: So you're either not taking (=) as primitive or you're stating the additional property that there exists (=) such that f = g === (= g) . f (from which you can easily show that (f . g) = h === (f = h) . g ). If you wanted to prove that bind is

Re: [Haskell-cafe] Ackermann Function Memoization, GHC Weird Output or Bug?

2008-03-14 Thread Cale Gibbard
Here's the bug: {-# INLINE safeIndex #-} safeIndex :: Ix i = (i, i) - Int - i - Int safeIndex (l,u) n i = let i' = unsafeIndex (l,u) i in if (0 = i') (i' n) then i' else error Error in array index unsafeIndex here is just

Re: Some clarity please! (was Re: [Haskell-cafe] Re: (flawed?) benchmark : sort)

2008-03-14 Thread Conor McBride
Hi On 14 Mar 2008, at 03:48, Roman Leshchinskiy wrote: Adrian Hey wrote: I would ask for any correct Eq instance something like the law: (x==y) = True implies x=y (and vice-versa) which implies f x = f y for all definable f which implies (f x == f y) = True (for expression types which are

[Haskell-cafe] HFuse: ls fails in HelloFS

2008-03-14 Thread Georg Neis
Hello, I've installed the HFuse package from hackage and am playing with the HelloFS example in the System/Posix/HFuse directory. The problem that I encounter is that listing the directory doesn't work: % ghc --make HelloFS.hs [1 of 1] Compiling Main ( HelloFS.hs, HelloFS.o )

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-14 Thread Adrian Hey
Dan Weston wrote: 6.3.2 (The Ord Class): The Ord class is used for totally ordered datatypes. This *requires* that it be absolutely impossible in valid code to distinguish equivalent (in the EQ sense, not the == sense) things via the functions of Ord. The intended interpretation of these

Re[2]: [Haskell-cafe] Problem making a program in ghc

2008-03-14 Thread Bulat Ziganshin
Hello Sterling, Friday, March 14, 2008, 7:06:24 AM, you wrote: yes, it's another question. my own program also writes to logfile and it got lock-free only when i've switched to using my own IO routines This answer may be way off base, but if differences appear between ghci and compiled

[Haskell-cafe] all threads are blocked by recvFrom

2008-03-14 Thread Vitaliy Akimov
Hello, I have a problem with building multithreaded UDP server. If main thread is waiting for new request in recvFrom all other threads are blocked too. I've checked every variant with forkIO,forkOS,-threaded etc, nothing's helped. After reading GHC docs I've understood this is happened becouse

[Haskell-cafe] FFI newbie question

2008-03-14 Thread Verma Anurag-VNF673
I am trying to figure out how to pass array of String (char **) from C to Haskell? I have read the FFI examples, but most of them are centered on calling C from Haskell. I have read in the mailing list, it is rare to call Haskell from C, but my requirement is such that I am going to write Haskell

Re: [Haskell-cafe] A question about monad laws

2008-03-14 Thread Wolfgang Jeltsch
Am Donnerstag, 13. März 2008 21:10 schrieben Sie: Not to be picky, but where did you hear that (==) established an equivalence relation? I think that’s the way it should be according to most Haskeller’s opinion. It might be true that the Haskell 98 report doesn’t say so but I think that many

Re: Some clarity please! (was Re: [Haskell-cafe] Re: (flawed?) benchmark : sort)

2008-03-14 Thread Roman Leshchinskiy
Conor McBride wrote: Hi On 14 Mar 2008, at 03:48, Roman Leshchinskiy wrote: Adrian Hey wrote: I would ask for any correct Eq instance something like the law: (x==y) = True implies x=y (and vice-versa) which implies f x = f y for all definable f which implies (f x == f y) = True (for

Re: [Haskell-cafe] FFI newbie question

2008-03-14 Thread John Meacham
On Fri, Mar 14, 2008 at 09:54:11PM +0800, Verma Anurag-VNF673 wrote: I am trying to figure out how to pass array of String (char **) from C to Haskell? I have read the FFI examples, but most of them are centered on calling C from Haskell. I have read in the mailing list, it is rare to call

[Haskell-cafe] Re: all threads are blocked by recvFrom

2008-03-14 Thread Vitaliy Akimov
Rebuilding of the network package with changed safety helped but I don't think this is the solution. BTW accept is declared as safe. What is the reason of declaring recvFrom as unsafe? I think this breaks highly required feature. Apparently it's impossible to make concurrent server for non

Re: [Haskell-cafe] Re: all threads are blocked by recvFrom

2008-03-14 Thread Adam Langley
On Fri, Mar 14, 2008 at 7:43 AM, Vitaliy Akimov [EMAIL PROTECTED] wrote: Rebuilding of the network package with changed safety helped but I don't think this is the solution. BTW accept is declared as safe. What is the reason of declaring recvFrom as unsafe? I think this breaks highly

Re: [Haskell-cafe] Re: all threads are blocked by recvFrom

2008-03-14 Thread Vitaliy Akimov
I assume that you're binding the libc function directly here: I'm using Network.Socket. Sory if it's not clear from my previous posts. In that case, you need to have the RTS manage sleeping your thread for you. You should make the socket non-blocking and handle the EAGAIN and EWOULDBLOCK

Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-03-14 Thread Wolfgang Jeltsch
Am Samstag, 2. Februar 2008 14:54 schrieben Sie: On Feb 1, 2008 10:32 PM, Wolfgang Jeltsch wrote: Am Freitag, 1. Februar 2008 13:00 schrieb Alfonso Acosta: […] To make it friendlier for the end user I thought about defining aliases for lets say the first 1 numbers using Template

Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-03-14 Thread Alfonso Acosta
On Fri, Mar 14, 2008 at 5:30 PM, Wolfgang Jeltsch [EMAIL PROTECTED] wrote: I have a feedback from my Grapefruit co-developer about those aliases in the type-level package. He told me that on his machine, building this package took about 15 minutes, obviously because the machine ran out of

Re: [Haskell-cafe] File I/O question

2008-03-14 Thread John Melesky
On Mar 12, 2008, at 4:07 PM, Andrew Coppin wrote: I'm trying to read the file from Notepad.exe while my Haskell program is still running - which takes about an hour. I'm not a Windows user, but... Is it possible that Notepad tries to write-lock by default (since it's an editor), and fails?

Re: [Haskell-cafe] Re: all threads are blocked by recvFrom

2008-03-14 Thread Adam Langley
On Fri, Mar 14, 2008 at 8:51 AM, Vitaliy Akimov [EMAIL PROTECTED] wrote: I assume that you're binding the libc function directly here: I'm using Network.Socket. Sory if it's not clear from my previous posts. Then everything should Just Work(tm). You might need to paste in code in order to

[Haskell-cafe] Specification for Eq?

2008-03-14 Thread apfelmus
Roman Leshchinskiy wrote: Should the report say something like a valid Eq instance must ensure that x == y implies f x == f y for all f? Probably not, since this requires structural equality which is not what you want for ADTs. Should it be for all f which are not part of the implementation of

Re: [Haskell-cafe] Re: all threads are blocked by recvFrom

2008-03-14 Thread Adam Langley
On Fri, Mar 14, 2008 at 10:13 AM, Adam Langley [EMAIL PROTECTED] wrote: See [1] for an example which works for me. (If you're on Windows, you probably need to wrap main in withSocketsDo) AGL -- Adam Langley [EMAIL PROTECTED] http://www.imperialviolet.org

Re: [Haskell-cafe] Space leak - help needed

2008-03-14 Thread Justin Bailey
On Thu, Mar 13, 2008 at 4:50 PM, Krzysztof Kościuszkiewicz [EMAIL PROTECTED] wrote: Retainers are thunks or objects on stack that keep references to live objects. All retainers of an object are called the object's retainer set. Now when one makes a profiling run, say with ./jobname +RTS

Re: [Haskell-cafe] File I/O question

2008-03-14 Thread Andrew Coppin
John Melesky wrote: On Mar 12, 2008, at 4:07 PM, Andrew Coppin wrote: I'm trying to read the file from Notepad.exe while my Haskell program is still running - which takes about an hour. I'm not a Windows user, but... Is it possible that Notepad tries to write-lock by default (since it's an

[Haskell-cafe] Type system

2008-03-14 Thread Andrew Coppin
Haskell has an expressive and powerful type system - which I love. It also has a seemingly endless list of weird and obscure type system extensions. And there are various things you can do in Haskell which *require* some pretty serious type system hackery. And yet, none of this happens in any

Re: [Haskell-cafe] Ackermann Function Memoization, GHC Weird Output or Bug?

2008-03-14 Thread Donnie Jones
Hello, It seems this bug has already been submitted: http://hackage.haskell.org/trac/ghc/ticket/2120 Thanks for the help. __ Donnie Jones On 3/14/08, Cale Gibbard [EMAIL PROTECTED] wrote: Here's the bug: {-# INLINE safeIndex #-} safeIndex :: Ix i = (i, i) - Int - i - Int safeIndex (l,u) n

[Haskell-cafe] Gtk2hs

2008-03-14 Thread Andrew Coppin
Just a short one... gtk2hs won't build on my [Linux] laptop. What's the best channel for seeking help with this? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Gtk2hs

2008-03-14 Thread Lennart Kolmodin
-BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Andrew Coppin wrote: | Just a short one... gtk2hs won't build on my [Linux] laptop. What's the | best channel for seeking help with this? The #haskell (on freenode) isn't bad. You'll probably get help pretty quick here, it's known to be very user

Re: [Haskell-cafe] Type system

2008-03-14 Thread David Menendez
On Fri, Mar 14, 2008 at 2:50 PM, Andrew Coppin [EMAIL PROTECTED] wrote: Haskell has an expressive and powerful type system - which I love. It also has a seemingly endless list of weird and obscure type system extensions. And there are various things you can do in Haskell which *require*

Re: [Haskell-cafe] Re: Implementing fixed-sized vectors (using datatype algebra?)

2008-03-14 Thread Wolfgang Jeltsch
Am Freitag, 14. März 2008 17:46 schrieben Sie: […] I think that removing aliases completely is not a good idea. How about generating much lower aliases for decimals (lets say until 1000), I don’t think, this is a good idea. Like nobody will need an alias for 8247, nobody will need an alias

Re: [Haskell-cafe] Gtk2hs

2008-03-14 Thread Andrew Coppin
Don Stewart wrote: andrewcoppin: Just a short one... gtk2hs won't build on my [Linux] laptop. What's the best channel for seeking help with this? Discuss it on the gtk2hs list, with a full error log. Thanks. I'll go look at that. (Who knows, maybe somebody already solved this

[Haskell-cafe] thanks for your feedback concerning tech documentation.

2008-03-14 Thread michael
Thanks. I was encouraged by this response I got. I'm ready to go. Since I'm trapped in the space-time continuum like most people, I can't do it all at once. I would like to. Anything that supports haskell is okay by me. My first area of interest is HAppS. I wrote some e-mail to them yesterday, but

Re: [Haskell-cafe] Type system

2008-03-14 Thread Dan Piponi
On Fri, Mar 14, 2008 at 11:50 AM, Andrew Coppin [EMAIL PROTECTED] wrote: Haskell has an expressive and powerful type system - which I love. It also has a seemingly endless list of weird and obscure type system extensions...And yet, none of this happens in any other programming language I've

Re: [Haskell-cafe] Type system

2008-03-14 Thread Don Stewart
dpiponi: On Fri, Mar 14, 2008 at 11:50 AM, Andrew Coppin [EMAIL PROTECTED] wrote: Haskell has an expressive and powerful type system - which I love. It also has a seemingly endless list of weird and obscure type system extensions...And yet, none of this happens in any other programming

[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-14 Thread Aaron Denney
On 2008-03-14, Conor McBride [EMAIL PROTECTED] wrote: Hi On 13 Mar 2008, at 23:33, Aaron Denney wrote: On 2008-03-13, Conor McBride [EMAIL PROTECTED] wrote: For a suitable notion of = on quotients, and with a suitable abstraction barrier at least morally in place, is that really too much

[Haskell-cafe] Re: Type system

2008-03-14 Thread Ben Franksen
Andrew Coppin wrote: Haskell has an expressive and powerful type system - which I love. It also has a seemingly endless list of weird and obscure type system extensions. And there are various things you can do in Haskell which *require* some pretty serious type system hackery. And yet, none

Re: [Haskell-cafe] Type system

2008-03-14 Thread Wolfgang Jeltsch
Am Freitag, 14. März 2008 19:50 schrieb Andrew Coppin: […] Is it because Haskell is used by more PhDs? Is it because Haskell actually allows you to implement constructs that are impossible in other languages? Is it because Haskell really provides greater type safety? Is it something else?

[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-14 Thread Aaron Denney
On 2008-03-14, Robert Dockins [EMAIL PROTECTED] wrote: Blah, blah, blah, its all in the documentation. The point is that making loose assumptions about the meaning of the operations provided by Eq and Ord complicates things in ways that can't be made to go away. Thanks. All of these seem

[Haskell-cafe] Re: Type system

2008-03-14 Thread Ben Franksen
Don Stewart wrote: As Manuel says, in C++ type level programming was an accident, in Haskell, it was by design. Was it, really? I was laways under teh impression that Oleg-style type system tricks were not in the least anticipated back when Haskell acquired type classes... Cheers Ben

[Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-14 Thread Aaron Denney
On 2008-03-10, Dan Weston [EMAIL PROTECTED] wrote: However, the report text is normative: 6.3.2 (The Ord Class): The Ord class is used for totally ordered datatypes. This *requires* that it be absolutely impossible in valid code to distinguish equivalent (in the EQ sense, not the ==

Re: [Haskell-cafe] Re: Type system

2008-03-14 Thread Lennart Augustsson
No, Haskell wasn't designed with type level programming in mind. In fact it took a few years before any serious type level programming was done. And lo and behold, the type level has an untyped logic language. -- Lennart On Fri, Mar 14, 2008 at 9:41 PM, Ben Franksen [EMAIL PROTECTED] wrote:

Re: [Haskell-cafe] Type system

2008-03-14 Thread Tillmann Rendel
Hi Andrew, Andrew Coppin wrote: Haskell has an expressive and powerful type system - which I love. It also has a seemingly endless list of weird and obscure type system extensions. And there are various things you can do in Haskell which *require* some pretty serious type system hackery.

Re: [Haskell-cafe] Re: Type system

2008-03-14 Thread Don Stewart
Yeah, I should clarify, this quote came up in relation to ATs, which are designed speifically to make type programming easier (unlike MPTCs and FDs, where it was an Olegian accident) lennart: No, Haskell wasn't designed with type level programming in mind. In fact it took a few years

Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-14 Thread John Meacham
Note that even if you wanted Eq to mean observational equality, you still can't perform that kind of reordering or 'sort' optimizations without running into trouble. for a not contrived at all example: data Id = Id { idIdent :: Int, idFreeVarCache :: [Id] } instance Eq Id where x == y =

[Haskell-cafe] deconstruction of the list/backtracking applicative functor?

2008-03-14 Thread Conal Elliott
Is there a known deconstruction of the list/backtracking applicative functor (AF)? If I decompose the list type into pieces (Maybe, product, composition), I think I can see where the ZipList AF comes from, but not the list/backtracking AF. Is there some construction simpler than lists

Re: [Haskell-cafe] HFuse: ls fails in HelloFS

2008-03-14 Thread Austin Seipp
Excerpts from Georg Neis's message of Fri Mar 14 06:38:02 -0500 2008: Hello, I've installed the HFuse package from hackage and am playing with the HelloFS example in the System/Posix/HFuse directory. As far as I know, the package uploaded onto hackage is merely a cabal-ised version of the