Re: [Haskell-cafe] Re: Language support for imperative code. Was: Re: monad subexpressions

2007-08-13 Thread Brian Hulley
Brian Hulley wrote: apfelmus wrote: Brian Hulley schrieb: main = do buffer - createBuffer edit1 - createEdit buffer edit2 - createEdit buffer splitter - createSplitter (wrapWidget edit1) (wrapWidget edit2) runMessageLoopWith splitter

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

2007-08-15 Thread Brian Hulley
Hi, On http://hackage.haskell.org/trac/haskell-prime/wiki/LambdaCase the proposed syntax for lambda case is: case of alts but this has a really bad downside for interactive editors: it doesn't allow one to distinguish between an incomplete construct and a completed construct thus

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

2007-08-15 Thread Brian Hulley
Stefan O'Rear wrote: 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

[Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Hi, I'm in the process of designing a little language inspired by Haskell but imperative, and have hit an issue regarding infix syntax which may be of interest also to anyone thinking about future revisions of Haskell or the problem of consistent parameter order in libraries. I'm wondering

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Brian Hulley wrote: I'm wondering if anyone can shed light on the reason why x # y gets desugared to (#) x y and not (#) y x Can anyone think of an example where the current desugaring of infix arguments gives the correct order when the function is used in a postfix application

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Jonathan Cast wrote: On Tue, 2007-09-25 at 19:18 +0100, Brian Hulley wrote: Brian Hulley wrote: I'm wondering if anyone can shed light on the reason why x # y gets desugared to (#) x y and not (#) y x Of course, this is all a consequence of the well-known failure

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Ryan Ingram wrote: My comments inlined below... On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote: let shiftLeftByThree = shiftL' 3 in map shiftLeftByThree [10, 78, 99, 102] let shiftLeftByThree = (`shiftL` 3) in ... Aha! but this is using section syntax which

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-25 Thread Brian Hulley
Dan Piponi wrote: On 9/25/07, Brian Hulley [EMAIL PROTECTED] wrote: ..I seem to dimly recall that there is a natural language somewhere that also uses it but I can't remember which one. Every permutation of [S,V,O] appears in 'nature': http://en.wikipedia.org/wiki/Word_order. Thanks

Re: [Haskell-cafe] Desugaring of infix operators is (always?) the wrong way round

2007-09-27 Thread Brian Hulley
Sam Hughes wrote: Brian Hulley wrote: ... For example, with the prefix definition of a function with multiple clauses, the function name at the start of each clause is already lined up since it must appear at the margin of the current layout block ... Or you could have everything

Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Brian Hulley
Krzysztof Kościuszkiewicz wrote: Fellow Haskellers, I wanted to experiment a bit with lists and sequences (as in Data.List and Data.Sequence), and I got stuck. I wanted to dynamically select processing function depending on cmdline argument: main = do args - getArgs let reversor =

Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Brian Hulley
Brian Hulley wrote: Krzysztof Kościuszkiewicz wrote: So the type of mapM_ used in the code is (Foldable t, Monad m) = (a - m b) - t a - m () I'd like to keep the generic Foldable t there when m is specialized to IO. I thought this would allow type of reversor to be specialized to (Foldable f

Re: [Haskell-cafe] Dynamic choice of reverse implementation

2007-09-28 Thread Brian Hulley
Krzysztof Kościuszkiewicz wrote: So the type of mapM_ used in the code is (Foldable t, Monad m) = (a - m b) - t a - m () I'd like to keep the generic Foldable t there when m is specialized to IO. I thought this would allow type of reversor to be specialized to (Foldable f) = [String] - f String

[Haskell-cafe] US Patent for the idea of using Haskell to implement UAX #9

2010-04-16 Thread Brian Hulley
Hi everyone, It's been a long time since I last posted to this list since I'm currently working on something that is not directly Haskell-related, but it still relates to functional programming in general. Anyway imagine my surprise when an innocent search for some keywords (I can't remember

Re: [Haskell-cafe] US Patent for the idea of using Haskell to implement UAX #9

2010-04-17 Thread Brian Hulley
Daniel Fischer wrote: Am Freitag 16 April 2010 20:50:25 schrieb Brian Hulley: revealed a link to a US Patent (7120900) for the idea of implementing the Unicode Bidirectional Algorithm (UAX #9 http://www.unicode.org/reports/tr9) in Haskell, making use, as far as I can tell, of nothing more than

Re: [Haskell-cafe] Re: US Patent for the idea ...

2010-04-17 Thread Brian Hulley
jerzy.karczmarc...@info.unicaen.fr wrote: Brian Hulley reports a search similar to : haskell unicode bidirectional Comment irrelevant to Haskell, sorry. Everybody does his/her various jobs. But I lost all respect due to people who work in the US Patent Office, when I saw the patent

Re: [Haskell-cafe] Re: US Patent for the idea ...

2010-04-17 Thread Brian Hulley
Murray Gross wrote: On Sat, 17 Apr 2010, Brian Hulley wrote: see the patent 6,368,227. The search site is here: http://patft.uspto.gov/netahtml/PTO/srchnum.htm Best regards. Jerzy Karczmarczuk ... It's really almost not fair to cite that particular patent, since, if I recall the story

Re: [Haskell-cafe] Editors for Haskell

2006-05-30 Thread Brian Hulley
Mathew Mills wrote: With Haskell's lovely strong static typing, it is a crying shame we don't have an editor with immediate feedback, ala Eclipse. I've started writing an editor for Haskell. (It will be a commercial product) The first prototype was in C - now I'm re-writing from scratch in

Re: [Haskell-cafe] Editors for Haskell

2006-05-30 Thread Brian Hulley
Benjamin Franksen wrote: On Tuesday 30 May 2006 20:59, Brian Hulley wrote: It is quite a tall order to provide immediate typed feedback of an edit buffer that will in general be syntactically incomplete but this is my eventual aim. One issue in the area of immediate feedback is that Haskell's

Re: [Haskell-cafe] Editors for Haskell

2006-05-31 Thread Brian Hulley
Doaitse Swierstra wrote: On 2006 mei 30, at 17:33, Brian Hulley wrote: But the buffer will nearly always be incomplete as you're editing it. I was kind of hoping that the syntax of Haskell could be changed so that for any sequence of characters there would be a unique parse that had a minimum

[Haskell-cafe] Re: Editors for Haskell

2006-06-01 Thread Brian Hulley
Thomas Hallgren wrote: Brian Hulley wrote: Another thing which causes difficulty is the use of qualified operators, and the fact that the qualification syntax is in the context free grammar instead of being kept in the lexical syntax (where I think it belongs). You are in luck, because

Re: [Haskell-cafe] Re: Editors for Haskell

2006-06-02 Thread Brian Hulley
Simon Marlow wrote: Malcolm Wallace wrote: Brian Hulley [EMAIL PROTECTED] wrote: Thanks for pointing this out. Although there is still a problem with the fact that var, qvar, qcon etc is in the context free syntax instead of the lexical syntax so you could write: 2 `plus

Re: [Haskell-cafe] FunDeps conflict

2006-06-06 Thread Brian Hulley
Joel Björnson wrote: Hi. I have a question regarding type classes and FunDeps. Consider the following code : class Class2 a b | a - b class IsFoo a data Bar a = Bar a instance IsFoo a = Class2 a a instance IsFoo a = Class2 (Bar a) a The last two instantiations will yield a 'Functional

Re: [Haskell-cafe] FunDeps conflict

2006-06-06 Thread Brian Hulley
Joel Björnson wrote: Hi. I have a question regarding type classes and FunDeps. Consider the following code : class Class2 a b | a - b class IsFoo a data Bar a = Bar a instance IsFoo a = Class2 a a instance IsFoo a = Class2 (Bar a) a The last two instantiations will yield a 'Functional

Re: [Haskell-cafe] FunDeps conflict

2006-06-06 Thread Brian Hulley
Brian Hulley wrote: Joel Björnson wrote: Hi. I have a question regarding type classes and FunDeps. Consider the following code : class Class2 a b | a - b class IsFoo a data Bar a = Bar a instance IsFoo a = Class2 a a instance IsFoo a = Class2 (Bar a) a The last two instantiations

Re: [Haskell-cafe] newbie type signature question

2006-06-09 Thread Brian Hulley
Brock Peabody wrote: Please excuse my newbiness, but in this snippet: data (Monad m) = DataType m = DataType { f :: Char - m () } test_function :: (Monad m) = DataType m - m () test_function d = f d 'C' Why is (Monad m) = required, when the definition

Re: Re[2]: [Haskell-cafe] newbie type signature question

2006-06-12 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Saturday, June 10, 2006, 3:05:25 AM, you wrote: It is possible that this feature was added to the language for the benefit of people who prefer not to use explicit type signatures but afaiu this goes against best practice where everything should always have

[Haskell-cafe] Everything but the lazyness - idea for force/delay lists

2006-06-12 Thread Brian Hulley
Hi - I've been thinking about how to get an extremely fast language with all the benefits of Haskell ie completely pure with no side effects, but with monads, higher order functions, type classes etc, but without the lazyness. I know this is controversial, but having started to write a

Re: [Haskell-cafe] Everything but the lazyness - idea for force/delay lists

2006-06-15 Thread Brian Hulley
is that the typeclasses and existentials that Haskell supports are an advantage over OCaml or SML, but that the lazyness is a real nusiance but with some extra effort it's possible to mostly get rid of it. Regards, Brian. mt 2006/6/13, Brian Hulley [EMAIL PROTECTED]: Hi - I've been thinking about

Re: [Haskell-cafe] what do you think of haskell ? (yes, it's a bit general ...:)

2006-06-15 Thread Brian Hulley
minh thu wrote: hi all folks, i'm diving into haskell for more than one year now. the reason for that is just that i like haskell. (i'm a computer science student) but i consider to move back to c/c++. There is also OCaml and SML, both of which have freely available compilers to generate

Re: [Haskell-cafe] do we have something like isDefined or isNullin Haskell?

2006-06-15 Thread Brian Hulley
On Thursday, June 15, 2006 8:07 PM Clifford Beshers wrote: On another note, who picked the word `Just' for this type and how did we end up with Some x | None in O'Caml and Just x | Nothing in Haskell? I've always thought this is one of the most charming things about Haskell, along with the

Re: [Haskell-cafe] Re: Functional programming for processing of largeraster images

2006-06-21 Thread Brian Hulley
Joel Reymont wrote: I think the issue wasn't using functional programming for large image processing, it was using Haskell. OCaml is notoriously fast and strict. Haskell/GHC is... lazy. Everyone knows that laziness is supposed to be a virtue. In practice, though, I'm one of the people who

Re: [Haskell-cafe] Functional progr., images, laziness and all the rest

2006-06-21 Thread Brian Hulley
[EMAIL PROTECTED] wrote: [snip] you may transform a recurrential equation yielding Y out of X: Y[n+1] = a*X[N+1] + b*Y[n] usually (imperatively) implemented as a loop, into a stream definition: filtr a b x@(x0:xq) = y where y = (x0:yq) yq = a*xq + b*y Can you explain how this transformation

Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Brian Hulley
Jerzy Karczmarczuk wrote: Brian Hulley wrote: [EMAIL PROTECTED] wrote: you may transform a recurrential equation yielding Y out of X: Y[n+1] = a*X[n+1] + b*Y[n] usually (imperatively) implemented as a loop, into a stream definition: ... Can you explain how this transformation

Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Brian Hulley
minh thu wrote: 2006/6/22, Brian Hulley [EMAIL PROTECTED]: Jerzy Karczmarczuk wrote: Brian Hulley wrote: [snip] y IS NOT a longer list than yq, since co-recursive equations without limiting cases, apply only to *infinite* streams. Obviously, the consumer of such a stream will generate

Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Brian Hulley
Jon Fairbairn wrote: On 2006-06-22 at 15:16BST Brian Hulley wrote: minh thu wrote: y and yq are infinite... But how does this change the fact that y still has 1 more element than yq? yq is after all, not a circular list. infinity+1 = infinity Surely this is just a mathematical convention

Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Brian Hulley
minh thu wrote: maybe i wrong, anyway : induction can be used to prove a property. we claim that the property is true for any finite i. so what's the property that you want to prove by induction ? you say 'by induction on the lenght of yq'.. but yq is just y (modulo the a*xq + b*). it's exactly

Re: [Haskell-cafe] Functional progr., images, laziness and alltherest

2006-06-22 Thread Brian Hulley
Stepan Golosunov wrote: On Thu, Jun 22, 2006 at 03:32:25PM +0100, Brian Hulley wrote: Bill Wood wrote: On Thu, 2006-06-22 at 15:16 +0100, Brian Hulley wrote: . . . But how does this change the fact that y still has 1 more element than yq? yq is after all, not a circular list. I don't see why

Re: [Haskell-cafe] Polymorphic type

2006-06-22 Thread Brian Hulley
Sara Kenedy wrote: Hello all, Now I am trying with the function of polymorphic type: This function returns the Nth element of list with type a. I try it as below. getNthElem :: Int - [a] - Maybe a getNthElemt _ [] = Nothing getNthElem 0 _ = Nothing getNthElem n s n length s = Nothing

Re: [Haskell-cafe] Functional progr., images, laziness and alltherest

2006-06-22 Thread Brian Hulley
Piotr Kalinowski wrote: On 22/06/06, Brian Hulley [EMAIL PROTECTED] wrote: ... This doesn't mean that these contradictions reflect reality - just that maths hasn't yet reached a true understanding of reality imho. Well, I for instance believe that contradiction IS the true nature of reality

[Haskell-cafe] Packages and modules

2006-06-25 Thread Brian Hulley
Hi - At the moment there is a problem in that two packages P and Q could contain the same hierarchical module eg Data.Foo, and the only way for user code to ensure the right Data.Foo is used is to ensure that packages P and Q are searched in the right order. However suppose P and Q also

Re: [Haskell-cafe] Packages and modules

2006-06-25 Thread Brian Hulley
David House wrote: Apologies to Brian for the multiple copies, this wasn't originally sent to the list. On 25/06/06, Brian Hulley [EMAIL PROTECTED] wrote: I'm wondering: would it not be easier to just make it that the package name is prepended to the hierarchical module name, so the modules

Re: [Haskell-cafe] Packages and modules

2006-06-25 Thread Brian Hulley
Robert Dockins wrote: On Sunday 25 June 2006 05:16 am, Brian Hulley wrote: [snip] I'm wondering: would it not be easier to just make it that the package name is prepended to the hierarchical module name, so the modules would instead be called by the names P.Data.Foo and Q.Data.Bar? [snip

Re: [Haskell-cafe] Packages and modules

2006-06-26 Thread Brian Hulley
Simon Peyton-Jones wrote: Simon and I have been thinking about fixing this, and we think we might actually do so for GHC 6.6. Your message provoked us to write up the design. It's here http://hackage.haskell.org/trac/ghc/wiki/GhcPackages Feedback welcome It's worth reading the old threads;

Re: [Haskell-cafe] how to write an haskell binding

2006-06-26 Thread Brian Hulley
minh thu wrote: about writing an haskell (or is it *a* haskell ?) binding for a c or a It is defnitely *a* haskell. There is actually no word in English with a silent 'h', though this statement is unfortunately controversial and news to whoever wrote the spell checker used in many printed

Re: [Haskell-cafe] how to write an haskell binding

2006-06-26 Thread Brian Hulley
Brian Hulley wrote: minh thu wrote * for c++, is it better to first write a c api for the c++ code before writing the binding [snip] class TimerFactory { static void Construct(); static void Destruct(); }; then the C api functions are given names like

Re: [Haskell-cafe] how to write an haskell binding

2006-06-27 Thread Brian Hulley
[EMAIL PROTECTED] wrote: Quoting Brian Hulley [EMAIL PROTECTED]: It is defnitely *a* haskell. There is actually no word in English with a silent 'h', though this statement is unfortunately controversial and news to whoever wrote the spell checker used in many printed publications

[Haskell-cafe] Are FunPtr's stable? (was: how to write an haskell binding)

2006-06-27 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Tuesday, June 27, 2006, 2:43:15 AM, you wrote: achieve a goal. One other thing to bear in mind is that foreign calls are extremely slow, so for example it is much faster to use the Foreign.Marshal.Array and Foreign.C.String functions to allocate and

Re: [Haskell-cafe] Re: how to write an haskell binding

2006-06-27 Thread Brian Hulley
Aaron Denney wrote: On 2006-06-27, Brian Hulley [EMAIL PROTECTED] wrote: [EMAIL PROTECTED] wrote: Quoting Brian Hulley [EMAIL PROTECTED]: It is defnitely *a* haskell. There is actually no word in English with a silent 'h', though this statement is unfortunately controversial and news

Re: [Haskell-cafe] Re: how to write an haskell binding

2006-06-27 Thread Brian Hulley
Jeremy Shaw wrote: At Tue, 27 Jun 2006 20:36:30 +0100, Brian Hulley wrote: What about words like 'hour' and 'honest'? Don't forget honor. So I'd say these two words are closely related, so the search is still on for another word with silent 'h' not related to time or integrity. How

Re: [Haskell-cafe] Are FunPtr's stable? (was: how to write an haskellbinding)

2006-06-28 Thread Brian Hulley
Simon Peyton-Jones wrote: Can I urge any of you who learn stuff that I wish I'd know at the beginning to add that information to GHC's FFI Wiki page? http://haskell.org/haskellwiki/GHC/Using_the_FFI Anyone can add to this material, and it's extremely helpful to jot down what you've learned while

Re: [Haskell-cafe] Packages and modules

2006-06-28 Thread Brian Hulley
Marc Weber wrote: I'm not sure on which mail of this thread I should append MHO. What happens if two programmers happen to choose the same package name? (Prepend the location on the filesystem? ;-) If something like a package name is introduced I would prefer not separating package and module

Re: [Haskell-cafe] Re: Where is Data.Atom?

2006-07-04 Thread Brian Hulley
Iain Alexander wrote: Another suggestion: Put your strings in an ordered binary tree (other data structures might also work here). Make your Atom an encoding of the structure of the tree (resp. other structure). This is logically a sequence of bits, 0 for left (less than), 1 for right

[Haskell-cafe] Re: Packages and modules

2006-07-04 Thread Brian Hulley
Simon Peyton-Jones wrote: Concerning other mail on this subject, which has been v useful, I've revised the Wiki page (substantially) to take it into account. http://hackage.haskell.org/trac/ghc/wiki/GhcPackages Further input (either by email or by adding material to the Wiki) would be welcome.

Re: [Haskell-cafe] Re: Packages and modules

2006-07-04 Thread Brian Hulley
Brian Hulley wrote: Simon Peyton-Jones wrote: http://hackage.haskell.org/trac/ghc/wiki/GhcPackages I think the following is a non-question: An open question: if A.B.C is in the package being compiled, and in an exposed package, and you say import A.B.C, do you get an error

[Haskell-cafe] Re: Packages and modules

2006-07-05 Thread Brian Hulley
Simon Peyton-Jones wrote: In response to Brian and Ian's helpful comments, I've added a bunch more stuff to our proposal about packages. If I have missed anything, let me know. http://hackage.haskell.org/trac/ghc/wiki/GhcPackages If you or anyone else thinks the choices made there are poor

[Haskell-cafe] Re: Packages and modules

2006-07-05 Thread Brian Hulley
Simon Peyton-Jones wrote: So instead of just taking this simple solution, the wiki proposal is instead destroying the beauty of the per-package namespace idea by incorporating into it the existing shared namespaces with their attendant problems, instead of just letting the existing messy system

Re: [Haskell-cafe] Re: Packages and modules

2006-07-06 Thread Brian Hulley
Brian Hulley wrote: Simon Peyton-Jones wrote: compulsory. Perhaps you could improve the wording to make it more unambiguous? Indeed, if we've converged, would you like to fold into our draft whatever you think is useful from yours? [snip] Therefore it seems best to just leave them

Re: [Haskell-cafe] help with creating a DAG?

2006-07-08 Thread Brian Hulley
David Roundy wrote: Hi all, I'm wanting to create a data structure to hold a directed acyclic graph (which will have patches represented by edges), and haven't yet been able to figure out a nice representation. I'd like one that can be reasoned with recursively, or as closely to recursively as

Re: [Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-12 Thread Brian Hulley
Christian Maeder wrote: Donald Bruce Stewart schrieb: Question over whether it should be: splitBy (=='a') aabbaca == [,,bb,c,] or splitBy (=='a') aabbaca == [bb,c] I argue the second form is what people usually want. Yes, the second form is needed for words, but the first form is

Re: [Haskell-cafe] Comma in the front

2006-07-14 Thread Brian Hulley
Tim Docker wrote: These layouts feel a bit artificial to me. I am quite partial to python's list syntax - a trailing comma is optional. meaning you can write [ a, b, c, ] I'm surprised this approach isn't more widespread - Are there reasons why haskell syntax could

Re: [Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-22 Thread Brian Hulley
Neil Mitchell wrote: And if someone wants to define a new and better FilePath type, I would prefer something more abstract, such as a list of Path components, with functions to serialize it as a String and to parse it from a String. A list of path components is just not enough, I'm afraid.

Re: [Haskell-cafe] Why Haskell?

2006-07-23 Thread Brian Hulley
Matthew Bromberg wrote: 3) The problem here is existing code. I don't want to add every function that I use into a class just to maintain simple polymorphism over closely related numeric types. This would take longer than just calling the coercion routines. It's funny how trivial stuff likes

Re: Re[2]: [Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-23 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Sunday, July 23, 2006, 1:20:36 AM, you wrote: instance IString ByteString.Char8 ... instance IString String ... i think that we should ask Donald Stewart who is patronized SoC project involving development of such type class. If he will say that such type

Re: [Haskell-cafe] Re: Why Haskell?

2006-07-24 Thread Brian Hulley
Simon Marlow wrote: Neil Mitchell wrote: Would it not be possible to add a GHC rule like the following: forall a b . sequence a b = sequence_ a b I'm not sure if thats correct, a valid rule definition, or semantics preserving, but if it was it would be nice :) Now there's a good idea!

Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Brian Hulley
Jon Fairbairn wrote: On 2006-07-27 at 13:01+0200 Tomasz Zielonka wrote: Also, after a few years of Haskell programming, I am still not sure how to indent if-then-else. what I was alluding to in my footnote... I think there's really only one way when it needs to occupy more than one line:

Re: [Haskell-cafe] Why does Haskell have the if-then-else syntax?

2006-07-27 Thread Brian Hulley
David House wrote: On 27/07/06, Brian Hulley [EMAIL PROTECTED] wrote: I think there's really only one way when it needs to occupy more than one line: if c then t else f Confusingly, if c then t else f Also works, although no-one really knows why. Only

Re: [Haskell-cafe] if-then-else as rebindable syntax (was Re: Why doesHaskell have the if-then-else syntax?)

2006-07-27 Thread Brian Hulley
Niklas Broberg wrote: Also, is cond the best name for the suggested function? If we don't expect anyone to really use it without the sugar, we could name it whatever weird thing so as to break as few existing programs as possible. It would make explicit import a bit more akward though. But I

[Haskell-cafe] The difficulty of designing a sequence class

2006-07-30 Thread Brian Hulley
Hi - Part 1 of 2 - Monoid versus MonadPlus === I've just run into a troublesome question when trying to design a sequence class: class ISeq c a | c - a where empty :: c single :: a - c append :: c - c - c However I've noticed that people

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-30 Thread Brian Hulley
Robert Dockins wrote: On Sunday 30 July 2006 07:47, Brian Hulley wrote: Another option, is the Edison library which uses: class (Functor s, MonadPlus s) = Sequence s where so here MonadPlus is used instead of Monoid to provide empty and append. So I've got three main questions: 1) Did

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
Robert Dockins wrote: On Jul 30, 2006, at 5:28 PM, Brian Hulley wrote: Robert Dockins wrote: So, what you want is a sequence of sequences that can be transparently converted to a flattened sequence and vice versa? Yes as long as the conversion between them takes no time at all

Fw: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
David Menendez wrote: Brian Hulley writes: 1) Did Edison choose MonadPlus just because this fitted in with the lack of multi-parameter typeclasses in H98? Instances of Monoid (and your ISeq) have kind *. Instances of MonadPlus (and Edison's Sequence) have kind * - *. Functions like map, zip

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
David Menendez wrote: [EMAIL PROTECTED] writes: I didn't get around to fixing Sequence because there wasn't a need for it yet, but yes, it should be done. That's a tough call to make. Changing the kind of Sequence to * from * - * means losing the Functor, Monad, and MonadPlus superclasses and

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
[EMAIL PROTECTED] wrote: G'day all. Quoting Brian Hulley [EMAIL PROTECTED]: The problem is that some people will be using Data.Edison.Seq at the moment and will naturally not want it to change. However I'd suggest that all the common operations be factored out into separate classes eg

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Brian Hulley
Brian Hulley wrote: David Menendez wrote: Brian Hulley writes: 4) Would it be worth reconsidering the rules for top level names so that class methods could always be local to their class (ditto for value constructors and field names being local to their type constructor). Qualified module

Re: Re[2]: [Haskell-cafe] The difficulty of designing a sequence class

2006-08-01 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Tuesday, August 1, 2006, 4:43:23 AM, you wrote: As you've pointed out, there are 2 separate issues that are in danger of being confused: 1) Forcing all sequence instances to support all operations 2) Bundling all the ops into a single huge class

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-08-01 Thread Brian Hulley
John Meacham wrote: On Tue, Aug 01, 2006 at 02:56:21AM +0100, Brian Hulley wrote: Now the problem is that person C may come along and notice that there is a useful abstraction to be made by inheriting both from ClassA and ClassB. But both of these define foo and there is no mechanism

Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley
Robert Dockins wrote: [snip other points] 7) Finally, I somehow feel like there should be a nice categorical formulation of these datastructure abstractions which would help to drive a refactoring of the API typeclasses in a principled way, rather than on an ad-hoc

Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley
Robert Dockins wrote: [snip] 7) Finally, I somehow feel like there should be a nice categorical formulation of these datastructure abstractions which would help to drive a refactoring of the API typeclasses in a principled way, rather than on an ad-hoc I-sort-of-think-these-go-together sort of

Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley
Jared Updike wrote: This page: http://jaortega.wordpress.com/2006/03/17/programmers-go-bananas/ lists some references at the bottom. Perhaps they would be useful. Thanks! That page looks really interesting and useful, Brian. ___ Haskell-Cafe

Re: [Haskell-cafe] Future Edison directions

2006-08-01 Thread Brian Hulley
Brian Hulley wrote: splitWith :: (v - Bool) - c - (c,c) splitWith p t | isEmpty t = (empty, empty) | p (measure t) = let (l,x,r) = splitWithInternal p mempty t in (l, pushL x r) | otherwise

Re: [Haskell-cafe] ANN: TextRegexLazy-0.56, (=~) and (=~~) are here

2006-08-02 Thread Brian Hulley
Chris Kuklewicz wrote: Announcing: TextRegexLazy version 0.56 Where: Tarball from http://sourceforge.net/projects/lazy-regex darcs get --partial [--tag=0.56] http://evenmere.org/~chrisk/trl/stable/ License : BSD, except for Great! - Thanks for all your hard work in making this available

[Haskell-cafe] Code review: initial factoring for sequences and other structures

2006-08-03 Thread Brian Hulley
Hi - I've started work on an initial factoring of sequence ops into classes, and already I've run into some major design issues which stand like a mountain in the way of progress. The classes are below: -- all code below standard BSD3 licence :-) module Duma.Data.Class.Foldable (

Re: [Haskell-cafe] Code review: initial factoring for sequences andother structures

2006-08-03 Thread Brian Hulley
Brian Hulley wrote: Hi - I've started work on an initial factoring of sequence ops into [snip] class Foldable c a | c - a where foldR :: (a - b - b) - b - c - b [snip] There is a general problem that when the element type needs to be specified along with the type of the overall

Re: [Haskell-cafe] a bunch of newbie questions

2006-08-04 Thread Brian Hulley
Mark T.B. Carroll wrote: Janis Voigtlaender [EMAIL PROTECTED] writes: (snip) Yes, as long as enough type information is provided for the typechecker to decide what is the correct instance to use. (snip) I've always been a little surprised when this doesn't happen more widely for things other

Re: [Haskell-cafe] a bunch of newbie questions

2006-08-04 Thread Brian Hulley
Martin Percossi wrote: Bulat Ziganshin wrote: this is called ad-hoc polymorphism which is not supported by Haskell. instead Haskell supports parametric polymorphism via type classes. I think you are wrong here Bulat. In fact, I think a) Haskell supports parametric polymorphism, e.g. id :: t

Re: [Haskell-cafe] Why Not Haskell?

2006-08-04 Thread Brian Hulley
Hans van Thiel wrote: Hello All, I'm wondering why I can't find any commercial Haskell applications on the Internet. Is there any reason for this? I'm actually working on a Haskell program which I hope to release as a commercial application. The biggest problem I'm encountering is the lack

Re: Re[2]: [Haskell-cafe] a bunch of newbie questions

2006-08-04 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Friday, August 4, 2006, 8:50:25 PM, you wrote: class Bar a b where bar :: a - b (*) But there's one exception: you can't use typeclasses to resolve overloadings between values and functions because non-function values don't have a

Re: [Haskell-cafe] Why shouldn't variable names be capitalized?

2006-08-04 Thread Brian Hulley
Martin Percossi wrote: Hi, I'm wondering what the rationale was for not allowing capitalized variable names (and uncapitalized type names and constructors). I can only think of two arguments, and IMHO both of them are bad: 1. Enforces a naming convention. Fine - but my view is that this doesn't

Re: [Haskell-cafe] Monad Imparative Usage Example

2006-08-05 Thread Brian Hulley
Kaveh Shahbazian wrote: Thanks All This is about my tries to understand monads and handling state - as you perfectly know - is one of them. I have understood a little about monads but that knowledge does not satidfy me. Again Thankyou There are many tutorials available from the wiki at

Re: [Haskell-cafe] Monad Imparative Usage Example

2006-08-05 Thread Brian Hulley
Brian Hulley wrote: q = (\x - p) For example with the State monad, (q) must be some expression which evaluates to something of the form S fq where fq is a function with type s - (a,s), and similarly, (\x - p) must have type a -S ( s - (a,s)). If we choose names for these values which describe

Re: [Haskell-cafe] Monad Imparative Usage Example

2006-08-05 Thread Brian Hulley
Ooops - more bugs in my explanation... Brian Hulley wrote: -- from State.hs newtype State s a = S (s - (a,s)) I used the source given in ghc-6.4.2\libraries\monads\Monad\State.hs but the version of state monad that comes with the hierarchical libs is in ghc-6.4.2\libraries\mtl\Control

Re: [Haskell-cafe] Why Not Haskell?

2006-08-05 Thread Brian Hulley
Henning Thielemann wrote: On Fri, 4 Aug 2006, Brian Hulley wrote: 4) Haskell is open source and licensing restrictions forbid commercial applications. I haven't seen any such restrictions, but is this a problem for the standard modules? You can discover the licensing situation by downloading

Re: [Haskell-cafe] Why Not Haskell?

2006-08-06 Thread Brian Hulley
Piotr Kalinowski wrote: On 06/08/06, Brian Hulley [EMAIL PROTECTED] wrote: Therefore I think this distinction between concepts is just sophistry. The distinction is there and relies on the community and people being honest to avoid situations as you described. If you don't want it however

Re: [Haskell-cafe] Re: Why Not Haskell?

2006-08-07 Thread Brian Hulley
Jón Fairbairn wrote: Stefan Monnier [EMAIL PROTECTED] writes: I can't entirely dismiss GNU/FSF/GPL but it poses a fundamental conflict with the only way I can see of earning a living so it's like a continuous background problem which drains some of my energy and enthusiasm hence the length of

Re: [Haskell-cafe] Re: Why Not Haskell?

2006-08-07 Thread Brian Hulley
Brian Hulley wrote: Jón Fairbairn wrote: Stefan Monnier [EMAIL PROTECTED] writes: I can't entirely dismiss GNU/FSF/GPL... Maybe you should thank the FSF for making you doubt: I know of several good ideas that started out as attempts at commercial projects but weren't taken up. [...snip

Re: [Haskell-cafe] How can we detect and fix memory leak due tolazyness?

2006-08-07 Thread Brian Hulley
Ahn, Ki Yung wrote: Recently, I'm facing the dark side of laziness -- the memory leak because of laziness. The following is the code that leaks memory. sctAnal gs = null cgs || all (not . null) dcs where gs' = fixSize compose $ Set.fromList [TT (x,y,cs) [] | To _ x y cs-Set.toList gs]

Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley
Tamas K Papp wrote: The code in the subject generates an error. I understand why this is (- is treated as part of the number), but I don't know how to solve it, ie how to tell Haskell that - is a function/binary operator? Actually looking at the Haskell98 report, -2 seems to be treated as

Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley
Jared Updike wrote: -4^2is not the same whether parsed as (-4)^2 or -(4^2) (the correct version) Basically, before someone argues this with me, -4^2 should parse the same as - 4^2 which should be the same thing as 0 - 4^2 I'd argue that -4^2 should parse as (-4)^2 in the same way

Re: [Haskell-cafe] A restricted subset of CPP included in a revisionof Haskell 98

2006-08-17 Thread Brian Hulley
On Thursday, August 17, 2006 7:54 PM, Brian Smith wrote: I want to have conditionals limited in their placement to make things easier for refactoring tools. But, I don't have any ideas about how to deal with conditional exports without allowing preprocessor conditionals in the export list.

Re: [Haskell-cafe] map (-2) [1..5]

2006-08-17 Thread Brian Hulley
Jared Updike wrote: I'd also argue that in maths the necessary brackets are implied by the superscripting syntax ASCII text parsing issues aside, in math, 2 -4 =? (No you cannot ask if there is space between the 4 and the - symbol, or if I meant (-4)^2 or -(4^2), or if I

  1   2   3   4   >