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

2008-02-11 Thread David Benbennick
On Feb 11, 2008 10:18 PM, Uwe Hollerbach <[EMAIL PROTECTED]> wrote: > If I fire up ghci, import > Data.Ratio and GHC.Real, and then ask about the type of "infinity", it > tells me Rational, which as far as I can tell is Ratio Integer...? Yes, Rational is Ratio Integer. It might not be a good idea

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

2008-02-11 Thread Uwe Hollerbach
Ratio Integer may possibly have the same trouble, or maybe something related. I was messing around with various operators on Rationals and found that positive and negative infinity don't compare right. Here's a small program which shows this; if I'm doing something wrong, I'd most appreciate it bei

[Haskell-cafe] Announce: Melbourne Functional Programming Union

2008-02-11 Thread Bernie Pope
Hello Haskellers, After a few years hiatus, I'm pleased to announce that the Melbourne Functional Programming Union (FPU) is back. What is the FPU? It is a group of people who are interested in all things functional programming. We hold regular informal talks, and have friendly discussions

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

2008-02-11 Thread Derek Elkins
On Mon, 2008-02-11 at 13:34 -0800, Stefan O'Rear wrote: > On Mon, Feb 11, 2008 at 01:59:09PM +, Neil Mitchell wrote: > > Hi > > > > > > (x >>= f) >>= g == x >>= (\v -> f v >>= g) > > > > > > Or stated another way: > > > > > > (x >>= f) >>= g == x >>= (f >>= g) > > > > Which is totally wrong,

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

2008-02-11 Thread jerzy . karczmarczuk
Richard A. O'Keefe comments: [floating point addition is not associative]] And this is an excellent example of why violating expected laws is BAD. The failure of floating point addition to be associative means that there are umpteen ways of computing polynomials, for example, and doing it

Re: [Haskell-cafe] example packages that use Storable in Hackage ??

2008-02-11 Thread Adam Langley
2008/2/11 Galchin Vasili <[EMAIL PROTECTED]>: > http://hackage.haskell.org/packages/archive/pkg-list.html .. what are > some packages that use Storable? binary and binary-strict at least. AGL -- Adam Langley [EMAIL PROTECTED] http://www.imperialviolet.

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

2008-02-11 Thread Richard A. O'Keefe
On 12 Feb 2008, at 10:35 am, David Benbennick wrote: Some months ago I pointed out that Ratio Int (which is an Ord instance) doesn't satisfy this property. I provided a patch to fix the problem, but my bug report was closed as wontfix: http://hackage.haskell.org/trac/ghc/ticket/1517. I'm not h

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

2008-02-11 Thread Richard A. O'Keefe
On 12 Feb 2008, at 4:35 am, Andrew Butterfield wrote: [floating point addition is not associative] And this is an excellent example of why violating expected laws is BAD. The failure of floating point addition to be associative means that there are umpteen ways of computing polynomials, for exa

Re: [Haskell-cafe] Re: Datatypes - Haskell

2008-02-11 Thread Don Stewart
ok: > On the subject of data types, I've recently seen Haskell code using > data Foo ... = Foo { ... } > where I would have used newtype instead of data. When is it a good > idea to avoid newtype? It depends what's in the ... If its just something with the same representation as an existin

Re: [Haskell-cafe] Re: Datatypes - Haskell

2008-02-11 Thread Richard A. O'Keefe
On the subject of data types, I've recently seen Haskell code using data Foo ... = Foo { ... } where I would have used newtype instead of data. When is it a good idea to avoid newtype? ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http

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

2008-02-11 Thread Ben Franksen
Dan Piponi wrote: > IOn Feb 11, 2008 9:46 AM, Miguel Mitrofanov <[EMAIL PROTECTED]> wrote: >> It's well known that "ListT m" monad violates this law in general >> (though it satisfies it for some particular monads m). For example, > > I went through this example in quite a bit of detail a while ag

Re: [Haskell-cafe] example packages that use Storable in Hackage ??

2008-02-11 Thread Thomas Schilling
Hm, there used to be an experimental search tool that could find packages by which packages they depended on. I can't find it, though, so I assume it has been removed in the meantime. On 11 feb 2008, at 22.28, Galchin Vasili wrote: Hello, http://hackage.haskell.org/packages/archive/p

Re: [Haskell-cafe] RFC: SAT solver using Cont/callCC for backtracking search

2008-02-11 Thread Denis Bueno
On Mon, Feb 11, 2008 at 5:05 PM, Don Stewart <[EMAIL PROTECTED]> wrote: > Have you thought about uploading it to hackage.haskell.org? > We've got some similar stuff up there already, > > http://hackage.haskell.org/cgi-bin/hackage-scripts/package/sat-1.1.1 > > so feel free to upload this code

Re: [Haskell-cafe] RFC: SAT solver using Cont/callCC for backtracking search

2008-02-11 Thread Don Stewart
dbueno: > Hi all, > > I've recently done a small Haskell port of some OCaml code from a > paper entitled "SAT-MICRO: petit mais costaud!" It's a tiny (one > emacs buffer for the algorithm, ~160 lines overall) DPLL SAT solver > with non-chronological backtracking, implemented using the Cont monad

[Haskell-cafe] RFC: SAT solver using Cont/callCC for backtracking search

2008-02-11 Thread Denis Bueno
Hi all, I've recently done a small Haskell port of some OCaml code from a paper entitled "SAT-MICRO: petit mais costaud!" It's a tiny (one emacs buffer for the algorithm, ~160 lines overall) DPLL SAT solver with non-chronological backtracking, implemented using the Cont monad and callCC. If anyo

[Haskell-cafe] Parsec: Transforming between parsers with different token streams

2008-02-11 Thread Maciej Podgurski
Hi, I'm writing a simple parser for a line-oriented language using Parsec. A group of lines is parsed by a parser that tokens are of type String. Each token is again parsed by a parser that tokens are of type Char (i.e. this parser has the Parsec type Parser a). Now I wrote a transforming fu

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

2008-02-11 Thread David Benbennick
On Feb 11, 2008 11:24 AM, Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote: > a < b && b < c => a < c > > If an Ord instances doesn't obey these laws than it's likely to make Set and > Map behave strangely. Some months ago I pointed out that Ratio Int (which is an Ord instance) doesn't satisfy this

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

2008-02-11 Thread Stefan O'Rear
On Mon, Feb 11, 2008 at 01:59:09PM +, Neil Mitchell wrote: > Hi > > > > (x >>= f) >>= g == x >>= (\v -> f v >>= g) > > > > Or stated another way: > > > > (x >>= f) >>= g == x >>= (f >>= g) > > Which is totally wrong, woops. > > See this page for lots of details about the Monad Laws and quite

Re: [Haskell-cafe] ANN: nano-hmac 0.2.0

2008-02-11 Thread Don Stewart
hitesh.jasani: > nano-hmac provides bindings to OpenSSL's HMAC interface. With this release > the > set of hashing functions supported is: MD5, SHA, SHA1, SHA224, SHA256, SHA384, > SHA512. > > If you're unfamiliar with HMAC's then you may want to check out the second > link > below where I expl

[Haskell-cafe] example packages that use Storable in Hackage ??

2008-02-11 Thread Galchin Vasili
Hello, http://hackage.haskell.org/packages/archive/pkg-list.html .. what are some packages that use Storable? Regards, Vasili ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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

2008-02-11 Thread Isaac Dupree
Alfonso Acosta wrote: So type-level + parametrized-data is my vote. But don't let's spend too much time discussing the name. ;-) Fair enough. type-level + parameterized-data it is then (unless someone else has a better suggestion). I'm going to begin coding now. hang on, "parametrized" or "p

Re: [Haskell-cafe] Create a list without duplicates from a list with duplicates

2008-02-11 Thread Dan Weston
Of course the most *general* way requires an Eq constraint: > List.nub :: Eq a => [a] -> [a] But there are better functions (already mentioned) with the less general Ord constraint. Int and String are instances of Ord. "some other user defined data type" probably is too, but if you mean "an

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

2008-02-11 Thread Wolfgang Jeltsch
Am Montag, 11. Februar 2008 16:35 schrieb Andrew Butterfield: > This is precisely Jerzy's point - you can have many mathematical laws as > you like but there is no guarantee that a programming languages > implementation will satisfy them. But people writing instances of type classes should take ca

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

2008-02-11 Thread Wolfgang Jeltsch
Am Montag, 11. Februar 2008 14:57 schrieb Michael Reid: > > Now it should be easier to see that this is simply associativity. It's > > easy enough to violate, if you want to - but I don't have any nice > > simple examples to hand. > > I have recently been reading a tutorial or paper where a Monad t

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

2008-02-11 Thread Wolfgang Jeltsch
Am Montag, 11. Februar 2008 18:17 schrieben Sie: > […] > As suggested by the pointer you provided, I redefined FSVec and tailV > using a transformating of Succ into a type synonym family (see the end > of this mail for its full definition) but it didn't help. Be careful! Type family support is s

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

2008-02-11 Thread Alfonso Acosta
Hi Dan, On Feb 10, 2008 6:08 PM, Dan Licata <[EMAIL PROTECTED]> wrote: > > > The ideal type for the function would be: > > > > > > vector :: [a] -> FSVec s a Well, I probably didn't express myself properly when writing "The ideal type", "the first type which comes to mind" would have been more ac

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

2008-02-11 Thread Dan Piponi
IOn Feb 11, 2008 9:46 AM, Miguel Mitrofanov <[EMAIL PROTECTED]> wrote: > It's well known that "ListT m" monad violates this law in general > (though it satisfies it for some particular monads m). For example, I went through this example in quite a bit of detail a while ago and wrote it up here: ht

Re: [Haskell-cafe] ANN: nano-hmac 0.2.0

2008-02-11 Thread gwern0
On 2008.02.11 09:42:44 -0800, Adam Langley <[EMAIL PROTECTED]> scribbled 0.5K characters: > On Feb 11, 2008 12:54 AM, Hitesh Jasani <[EMAIL PROTECTED]> wrote: > > nano-hmac provides bindings to OpenSSL's HMAC interface. With this release > > the > > set of hashing functions supported is: MD5, SH

Re: [Haskell-cafe] fast integer base-2 log function?

2008-02-11 Thread Uwe Hollerbach
Thanks, guys! It looks at first glance as if the code Thorkil posted is similar to mine (grow comparison number in steps of 2 in the exponent, then binary-search to get the exact exponent), while Stefan's version is more similar to the walk-the-list idea I had in mind. I'll play with both of these

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

2008-02-11 Thread Miguel Mitrofanov
(x >>= f) >>= g == x >>= (\v -> f v >>= g) However, this seems to me a kind of mathematical identity. If it is mathematical identity, a programmer need not care about this law to implement a monad. Can anyone give me an example implementation of monad that violate this law ? It's well known tha

Re: [Haskell-cafe] Compulsory relation 1 to many from entity A to entity A

2008-02-11 Thread Justin Bailey
On Feb 9, 2008 2:12 AM, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: > I'd like to build a database model with winHugs that allows > a "recursive relation". For example a single instance of > entity "components" is related with at least another row of > the entity "components" (1 to many relationsh

Re: [Haskell-cafe] ANN: nano-hmac 0.2.0

2008-02-11 Thread Adam Langley
On Feb 11, 2008 12:54 AM, Hitesh Jasani <[EMAIL PROTECTED]> wrote: > nano-hmac provides bindings to OpenSSL's HMAC interface. With this release > the > set of hashing functions supported is: MD5, SHA, SHA1, SHA224, SHA256, SHA384, > SHA512. Just a heads up; PHO has written nice bindings to much

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

2008-02-11 Thread Alfonso Acosta
Hi Wolfgang, On Feb 10, 2008 5:43 PM, Wolfgang Jeltsch <[EMAIL PROTECTED]> wrote: I added some line annotations to the code below so that errors can be more easily understood > > (<+>) :: Add s1 s2 s3 => FSVec s1 a -> FSVec s2 a -> FSVec s3 a -- line 78 > > NullV <+> ys = ys -- line 79 > > (x

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

2008-02-11 Thread Jonathan Cast
On 11 Feb 2008, at 7:52 AM, Arnar Birgisson wrote: Hi all, On Feb 11, 2008 3:14 PM, apfelmus <[EMAIL PROTECTED]> wrote: I will be mean by asking the following counter question: x + (y + z) = (x + y) + z is a mathematical identity. If it is a mathematical identity, a programmer need not ca

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

2008-02-11 Thread Andrew Butterfield
Andrew Butterfield wrote: let m denote the "list monad" (hypothetically). Let's instantiate: return :: x -> [x] return x = [x,x] (>>=) :: [x] -> (x -> [y]) -> [y] xs >>= f = concat ((map f) xs) Let g n = [show n] Here (return 1 >>= g ) [1,2,3] = ["1","1","1","1","1","1"] but g[1,2,3] = [

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

2008-02-11 Thread Arnar Birgisson
Hi all, On Feb 11, 2008 3:14 PM, apfelmus <[EMAIL PROTECTED]> wrote: > I will be mean by asking the following counter question: > >x + (y + z) = (x + y) + z > > is a mathematical identity. If it is a mathematical identity, a > programmer need not care about this law to implement addition + . C

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

2008-02-11 Thread Felipe Lessa
On Feb 11, 2008 1:35 PM, Andrew Butterfield <[EMAIL PROTECTED]> wrote: > Hugs> 1.0 + (2.5e-15 + 2.5e-15) > 1.01 :: Double > Hugs> (1.0 + 2.5e-15) + 2.5e-15 > 1.0 :: Double Prelude> (1e30 + (-1e30)) + 1 1.0 Prelude> 1e30 + ((-1e30) + 1) 0.0 I love this example from David Goldberg (http

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

2008-02-11 Thread Andrew Butterfield
apfelmus wrote: Deokjae Lee wrote: Tutorials about monad mention the "monad axioms" or "monad laws". The tutorial "All About Monads" says that "It is up to the programmer to ensure that any Monad instance he creates satisfies the monad laws". The following is one of the laws. (x >>= f) >>= g =

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

2008-02-11 Thread Jonathan Cast
On 11 Feb 2008, at 5:33 AM, Deokjae Lee wrote: Tutorials about monad mention the "monad axioms" or "monad laws". The tutorial "All About Monads" says that "It is up to the programmer to ensure that any Monad instance he creates satisfies the monad laws". The following is one of the laws. (x >>

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

2008-02-11 Thread apfelmus
Deokjae Lee wrote: Tutorials about monad mention the "monad axioms" or "monad laws". The tutorial "All About Monads" says that "It is up to the programmer to ensure that any Monad instance he creates satisfies the monad laws". The following is one of the laws. (x >>= f) >>= g == x >>= (\v -> f

[Haskell-cafe] f(g(x), h(y)) - Correct syntax

2008-02-11 Thread [EMAIL PROTECTED]
Hallo! I have this code: q1 :: EName -> [ApprenticeInfo] q1 c = [apprenticeInfo n | n <- allApprentices, member ((sq4 c) (firstOf5(n))) == True] sq4 :: ESurname -> [IDB] sq4 c = (sq3 (sq1 (c))) firstOf5 :: (a,b,c,d,e) -> a firstOf5 (n,_,_,_,_) = n member

Re: [Haskell-cafe] f(g(x), h(y)) - Correct syntax

2008-02-11 Thread Henning Thielemann
On Mon, 11 Feb 2008, [EMAIL PROTECTED] wrote: > Hallo! > > I have this code: > > q1 :: EName -> [ApprenticeInfo] > q1 c = [apprenticeInfo n | n <- allApprentices, member ((sq4 > c) (firstOf5(n))) == True] > > sq4 :: ESurname -> [IDB] > sq4 c = (sq3 (sq1 (c

Re: [Haskell-cafe] f(g(x), h(y)) - Correct syntax

2008-02-11 Thread Luke Palmer
On Feb 11, 2008 2:27 PM, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote: > Hallo! > > I have this code: > > q1 :: EName -> [ApprenticeInfo] > q1 c = [apprenticeInfo n | n <- allApprentices, member ((sq4 > c) (firstOf5(n))) == True] > > sq4 :: ESurname -> [IDB]

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

2008-02-11 Thread jerzy . karczmarczuk
Deokjae Lee cites: The tutorial "All About Monads" says that "It is up to the programmer to ensure that any Monad instance he creates satisfies the monad laws". The following is one of the laws. (x >>= f) >>= g == x >>= (\v -> f v >>= g) However, this seems to me a kind of mathematical id

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

2008-02-11 Thread Neil Mitchell
Hi > > (x >>= f) >>= g == x >>= (\v -> f v >>= g) > > Or stated another way: > > (x >>= f) >>= g == x >>= (f >>= g) Which is totally wrong, woops. See this page for lots of details about the Monad Laws and quite a nice explanation of where you use them: http://www.haskell.org/haskellwiki/Monad_L

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

2008-02-11 Thread Michael Reid
> Now it should be easier to see that this is simply associativity. It's > easy enough to violate, if you want to - but I don't have any nice > simple examples to hand. > > I have recently been reading a tutorial or paper where a Monad that violated this law was presented. The authors shrugged it o

Re: [Haskell-cafe] Haskell Weekly News - February 10, 2008

2008-02-11 Thread Ross Paterson
On Mon, Feb 11, 2008 at 02:24:19PM +0100, Wolfgang Jeltsch wrote: > Am Montag, 11. Februar 2008 02:09 schrieb Don Stewart: > > [???] > > > * Imlib 0.1.1. Uploaded by Cale Gibbard. [120]Imlib: Added by > >CaleGibbard, Sun Jan 13 22:26:59 PST 2008.. > > > [???] > > > * haddock 2.

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

2008-02-11 Thread Neil Mitchell
Hi > The following is one of the laws. > > (x >>= f) >>= g == x >>= (\v -> f v >>= g) Or stated another way: (x >>= f) >>= g == x >>= (f >>= g) Now it should be easier to see that this is simply associativity. It's easy enough to violate, if you want to - but I don't have any nice simple exampl

[Haskell-cafe] A question about "monad laws"

2008-02-11 Thread Deokjae Lee
Tutorials about monad mention the "monad axioms" or "monad laws". The tutorial "All About Monads" says that "It is up to the programmer to ensure that any Monad instance he creates satisfies the monad laws". The following is one of the laws. (x >>= f) >>= g == x >>= (\v -> f v >>= g) However, th

Re: [Haskell-cafe] Haskell Weekly News - February 10, 2008

2008-02-11 Thread Wolfgang Jeltsch
Am Montag, 11. Februar 2008 02:09 schrieb Don Stewart: > […] > * Imlib 0.1.1. Uploaded by Cale Gibbard. [120]Imlib: Added by >CaleGibbard, Sun Jan 13 22:26:59 PST 2008.. > […] > * haddock 2.0.0.0. Uploaded by David Waern. [147]haddock: Added by >DavidWaern > […] What'

Re: [Haskell-cafe] using the writer monad to better understand foldl and foldr, and haskell debugging techniques in general

2008-02-11 Thread Felipe Lessa
On Feb 11, 2008 7:53 AM, Felipe Lessa <[EMAIL PROTECTED]> wrote: > read that IORef and do a big tell to the outside Writer monad. I'd say > that this is a safe use of unsafePerformIO as it shouldn't break > referential transparency. But without this hack I don't think we could Well, not really as

Re: [Haskell-cafe] using the writer monad to better understand foldl and foldr, and haskell debugging techniques in general

2008-02-11 Thread Felipe Lessa
On Feb 10, 2008 9:52 PM, Thomas Hartman <[EMAIL PROTECTED]> wrote: > So, I would say this proves my main point, which was that you could > accomplish the same thing using the writer monad that you could do > using the more "ad hoc" trace function from Debug.Trace. Not really. That only happens wit

Re: [Haskell-cafe] Newbie question: mutually exclusive strict / lazy

2008-02-11 Thread Loup Vaillant
2008/2/11, Peter Verswyvelen <[EMAIL PROTECTED]>: > > Yes, sorry, GHC's strictness analyzer. > > What I meant with this email is that I guess that for a strictness analyzer, > the information that a function is strict in an argument *independent from > the other arguments* would not be good enough

[Haskell-cafe] ANN: nano-hmac 0.2.0

2008-02-11 Thread Hitesh Jasani
nano-hmac provides bindings to OpenSSL's HMAC interface. With this release the set of hashing functions supported is: MD5, SHA, SHA1, SHA224, SHA256, SHA384, SHA512. If you're unfamiliar with HMAC's then you may want to check out the second link below where I explain a little bit about them in a

RE: [Haskell-cafe] Newbie question: mutually exclusive strict / lazy

2008-02-11 Thread Peter Verswyvelen
Yes, sorry, GHC's strictness analyzer. What I meant with this email is that I guess that for a strictness analyzer, the information that a function is strict in an argument *independent from the other arguments* would not be good enough in itself for optimization, it would be better to also us