Re: Standard Haskell

1997-08-20 Thread Jon . Fairbairn
or example) Haskell 1.4 And then compilers could always say "Not interested in compiling Haskell 1.4 programmes"... I don't think I like this though: it's an extra feature, and the whole point of the standardisation effort is to replace features by orthogonality (I hope). Jo

Re: length that yields Integer - Int is a WART

1997-08-25 Thread Jon . Fairbairn
coding. Jon -- Jon Fairbairn [EMAIL PROTECTED]

List administration question

1997-08-25 Thread Jon . Fairbairn
if this has been discussed and rejected already. Jon -- Jon Fairbairn [EMAIL PROTECTED]

Re: length that yields Integer - Int is a WART

1997-08-25 Thread Jon . Fairbairn
to think before using the Int version. PS. Hi Jon! Hej Lennart! -- Jon Fairbairn [EMAIL PROTECTED] 18 Kimberley Road[EMAIL PROTECTED] Cambridge CB4 1HH +44 1223 570179 (pm only, please)

RE: Heap Sort

1997-10-04 Thread Jon . Fairbairn
originally, mergesort is somewhat faster in the average case. -- Jon Fairbairn [EMAIL PROTECTED] 18 Kimberley Road[EMAIL PROTECTED] Cambridge CB4 1HH +44 1223 570179 (pm only, please)

Re: Heap sort

1997-09-20 Thread Jon . Fairbairn
On 19 Sep, Nicholas Bleakly wrote: Does any body have a heap sort algorithm (i.e. takes a single unsorted list and applies a heap sort to it)? If you mean a functional one, I have. I could email it to you. Or post it here if wanted. Does anyone else have one? -- Jon Fairbairn

Re: Heap Sort

1997-10-07 Thread Jon . Fairbairn
rompted me to write it in the first place. [1] Fredman, Sedgewick, Sleator, and Tarjan. "The pairing heap: A new form of self-adjusting heap" Algorithmica 1(1):111-129, 1986. Many thanks for this reference, of which I was unaware. Jon -- Jon Fairbairn

group, groupBy

1997-10-10 Thread Jon . Fairbairn
obviously won't give the behaviour Carsten intended and which I think is the more natural. ie groupBy op ought to return a list of lists where each member is in order under `op`. Is there some good technical reason why we want the present groupBy? Jon -- Jon Fairbairn

Worst case for multipass pairing sort

1997-11-11 Thread Jon . Fairbairn
myself. Jon -- Jon Fairbairn [EMAIL PROTECTED] 18 Kimberley Road[EMAIL PROTECTED] Cambridge CB4 1HH +44 1223 570179 (pm only, please)

Re: standard Haskell

1997-12-11 Thread Jon . Fairbairn
that way indefinitely. I think 'indefinitely' here means 'until something goes wrong with nerdscaphe'. I suppose John could implement something using cookies, but why should he put in so much effort? Jon -- Jon Fairbairn [EMAIL PROTECTED]

Re: Standard Haskell Libraries

1998-04-24 Thread Jon . Fairbairn
Haskell committe - let's hope some of them are listening. Jon -- Jon Fairbairn [EMAIL PROTECTED]

Re: let succ be an Enum class member

1998-05-12 Thread Jon . Fairbairn
and toEnum to their overloaded types: toEnum :: Integral i = i - a fromEnum :: Integral i = a - i would that suit? -- Jon Fairbairn [EMAIL PROTECTED]

Syntax dubion

1998-06-26 Thread Jon . Fairbairn
+1 | pati+1 varop(r,i) rpati ie no () and no extra arguments, but given that one may want to define higher order functions this way, we ought to make the language allow it. Can anyone argue against it? -- Jon Fairbairn [EMAIL PROTECTED

Re: simple interface to web?

1998-07-13 Thread Jon . Fairbairn
with some extra exceptions for things such as connexion timed out and so on). -- Jon Fairbairn [EMAIL PROTECTED] 18 Kimberley Road[EMAIL PROTECTED] Cambridge CB4 1HH +44 1223 570179 (pm only, please)

Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-14 Thread Jon . Fairbairn
Haskell 2 to happen swiftly too! Jon -- Jon Fairbairn [EMAIL PROTECTED] 18 Kimberley Road[EMAIL PROTECTED] Cambridge CB4 1HH +44 1223 570179 (pm only, please)

Re: GHC/Hugs Status (was Re: simple interface to web?)

1998-07-16 Thread Jon . Fairbairn
Haskell ought to be easier if less is in the Prelude and more in libraries. Jon -- Jon Fairbairn [EMAIL PROTECTED] 18 Kimberley Road[EMAIL PROTECTED] Cambridge CB4 1HH +44 1223 570179 (pm only, please)

RE: Monomorphism

1998-07-21 Thread Jon . Fairbairn
of computing at Integer and converting at the end, an option that is not necessarily available. Incidentally, length :: Integral a = [b] - a, I think. Jon -- Jon Fairbairn [EMAIL PROTECTED]

Re: Rambling on numbers in Haskell

1998-08-03 Thread Jon . Fairbairn
a citizen of the world of existing numbers. Right, but it should be done via a class hierarchy, not by squishing all the numbers into one type. -- Jon Fairbairn [EMAIL PROTECTED]

Re: Rambling on numbers in Haskell

1998-08-03 Thread Jon . Fairbairn
is meaningful it doesn't usually give an int result. What you get back should depend on what you use it for. -- Jon Fairbairn [EMAIL PROTECTED] 18 Kimberley Road[EMAIL PROTECTED] Cambridge CB4 1HH +44 1223 570179 (pm

Re: some Standard Haskell issues

1998-08-07 Thread Jon . Fairbairn
that it's easier to learn to write -- --- than to learn not to try to define --, |--, --| and so on. Oh, and what is {-- comment --} under the present rules? Jon -- Jon Fairbairn [EMAIL PROTECTED]

Re: Int vs Integer

1998-09-10 Thread Jon . Fairbairn
the fact that you call a good library isn't relevant; what's important is what you do when you don't _need_ to use GMP to get the answer. My guess is that most of the real cost of doing Int sized arithmetic in Integers is the cost of detecting overflow. -- Jon Fairbairn

Re: Int vs Integer

1998-09-14 Thread Jon . Fairbairn
it also possible to reduce the number of checks for sequences of operations? -- Jon Fairbairn [EMAIL PROTECTED] 18 Kimberley Road[EMAIL PROTECTED] Cambridge CB4 1HH +44 1223 570179 (pm only, please)

Fwd: Re: Int vs Integer

1998-09-15 Thread Jon . Fairbairn
that too! Given that the report already mentions the 'specialize' pragma, I don't see any reason why the newly overloaded functions shouldn't be accompanied by specialisations for both Integer and Int, which should remove the efficiency drawback of making this change. Jon -- Jon Fairbairn

Re: Int vs Integer

1998-09-24 Thread Jon . Fairbairn
think there is a strong case of providing most of those operations on Integer too (perhaps at a different type). -- Jon Fairbairn [EMAIL PROTECTED]

RE: MonadZero (concluded?)

1998-11-05 Thread Jon . Fairbairn
of anything better than these monsters. um, monadZero, monadFail? People who can't type can always add their own renamings. -- Jon Fairbairn [EMAIL PROTECTED]

Re: Haskell 98 progress...

1998-11-23 Thread Jon . Fairbairn
confusing. Apologies if this is dragging up old arguments. Likewise! -- Jon Fairbairn [EMAIL PROTECTED]

Re: Type casting??

1999-03-11 Thread Jon . Fairbairn
or write foo :: Int - [Char] foo 0 = [] foo x = ['1'] ++ foo (x - 1) to declare it yourself. Note that type casting in the C sense is not available in Haskell, the only thing you can do is to restrict something to have fewer types than it otherwise would have. Jon -- Jon

Re: View on true ad-hoc overloading.

1999-05-20 Thread Jon . Fairbairn
On 20 May, Kevin Atkinson wrote: Sorry typo. That should be optional. Is this a job for overloading? I think it would be better to provide some syntactig sugar and compile-time checks for something like this: data Argtype = Arg {a::Int, b::Bool, c::Char} arg = Arg {a = 1, b = True, c =

RE: Proposal: Substring library for Haskell

1999-05-20 Thread Jon . Fairbairn
On 20 May, Frank A. Christoph wrote: I would welcome either. However, there is a huge body of code that assumes strings are lists of chars. Yes, obviously... this is for new programs (which people aren't writing because of Haskell's inefficiency in dealing with strings).

Re: Language Feature Request: String Evaluation

1999-06-08 Thread Jon . Fairbairn
On 8 Jun, Paul Hudak wrote: show x should be a string that when printed looks like the value that you would have to type to generate it directly. This example is most instructive: [...] and this is just cute: main = putStr (quine q) quine s = s ++ show s q = "main = putStr (quine

Re: Deriving Enum

1999-07-13 Thread Jon . Fairbairn
On 11 Jul, Wolfram Kahl wrote: Koen Claessen [EMAIL PROTECTED] proposes the following diagonalisation function: [ (a,b) | (a,b) - [1..] // [1..] ] For a suitable definition of (//), for example: (//) :: [a] - [b] - [(a,b)] xs // ys = diagonalize 1

Re: Deriving Enum

1999-07-13 Thread Jon . Fairbairn
On 13 Jul, Wolfram Kahl wrote: I confess guilty to have diverged from this simpler problem (//) :: [a] - [b] - [(a,b)] to the more general problem ??? like diagonalise:: [[a]] - [a] diagonalise l = d [] l d [] [] = [] d acc [] = -- d [] acc would do, but

Student project: error messages (was RE: Question)?

1999-08-20 Thread Jon . Fairbairn
On 19 Aug, Mark P Jones wrote: [...] note that the error messages that prompted Jon's comment didn't have anything to do with sophisticated type systems. Dealing with those kinds of things requires some hard work, but it isn't research, and so it's hard to justify, at least in an academic

Re: Question

1999-08-19 Thread Jon . Fairbairn
On 20 Aug, Bob Howard wrote: data BTree Integer = Leaf Integer | Node Integer (BTree Integer) (BTree Integer) ^ this ought to be a type variable name, but you've put the name of a type. mkTree :: Integer - BTree ^

Re: Haskell Wish list: library documentation

1999-09-08 Thread Jon . Fairbairn
On 8 Sep, George Russell wrote: Don't add more functions like concatSep to the standard library or prelude. Certainly not to the prelude, but I think there is a strong case for evolving the standard library based on what people use. I use ((concat .) intersperse) quite a lot, and having a

Re: Haskell Wish list: library documentation

1999-09-09 Thread Jon . Fairbairn
On 9 Sep, George Russell wrote: Here is my revised version of the documentation. my :-) (which incorporates some of the other suggestions.) I've given reasons at the bottom. Type: unzip :: [(a,b)] - ([a],[b]) unzip takes a list of pairs and returns a pair of lists. Definition:

Re: tuple component functions

1999-09-16 Thread Jon . Fairbairn
On 16 Sep, Keith Wansbrough wrote: I suggest calling them "pi13" or "prj13" rather than "tuple31", though. pi1_3 or proj1_3 or select_1_3 or sel_1_3, even s_1_3 -- omitting the "_" means sel is ambiguous (!). We should choose a scheme that can cope with such things even if they are

New mailing list (Was Re: Mailing lists down for a while, should be back up now)

1999-09-27 Thread Jon . Fairbairn
On 27 Sep, Manuel M. T. Chakravarty wrote: Antti-Juhani Kaijanaho [EMAIL PROTECTED] wrote, Please don't define lists by who'll use them. Define them by the topic of discussion. Good point. `haskell-help' or some such is definitely better. 'haskell-questions'? Maybe this list

Reverse composition

1999-10-08 Thread Jon . Fairbairn
Some time ago there was a discussion about what to call reverse composition (I can't find it in the archive - needs a search option?) Just now I thought of .~ from . for composition and ~ (tilde, but commonly called twiddle) for twiddling the order about. Maybe we could adopt that as normal

Re: [haskell] Reverse composition

1999-10-08 Thread Jon . Fairbairn
On 8 Oct, Christopher Jeris wrote: Personal taste in infix operators seems to be another good argument for a camlp4-style preprocessor for Haskell. Please no! I want to be able to read other folks programmes and vice versa. The whole point of suggesting a particular glyph on this foram

Re: Reverse composition

1999-10-08 Thread Jon . Fairbairn
On 8 Oct, Jonathan King wrote: I think you might see the point. (No pun back there, I promise...) I understand where using "." to mean composition came from, and I know that it's a long-standing tradition in at least the Haskell community, but I don't think the visual correspondence of

Re: Reverse composition

1999-10-08 Thread Jon . Fairbairn
On 8 Oct, Joe English wrote: [I wrote]: Just now I thought of .~ from . for composition and ~ (tilde, but commonly called twiddle) for twiddling the order about. I've also seen .| and |. used for this purpose (by analogy with Unix pipes.) John Hughes' Arrow library spells it "",

Idiomatic Haskell extension library (Re: Reverse composition)

1999-10-09 Thread Jon . Fairbairn
On 9 Oct, Heribert Schuetz wrote: [(f | g) x = f (g x); (f | g) x = g (f x)] "Use symmetric glyphs for commutative operations and asymmetric glyphs for non-commutative operations. Reflect glyphs for flipped operations." That would make me happy. which I would suggest as a general

Re: deleteBy type

1999-12-05 Thread Jon Fairbairn
Is not deleteBy :: (a-Bool) - [a] - [a] more natural for the library than deleteBy :: (a-a-Bool) - a - [a] - [a] ? I'd say so. In general the prelude seems rather weak on functions to manipulate predicates. Jón -- Jón Fairbairn

Re: string to Integer

2000-04-07 Thread Jon Fairbairn
Then, the question is why we write result = function operand1 operand2 instead of operand1 operand2 function = result I actually think the latter is cooler. :) I think there may be cultural influences about word order and/ or writing direction creeping in here :-) -- Jón Fairbairn

Re: more detailed explanation about forall in Haskell

2000-05-17 Thread Jon Fairbairn
I'm reluctant to get involved in this discussion, cheifly because it seems to me that Jan is attacking a position that has quite a long history with (inter alia) the argument that a different position has a longer history, which doesn't strike me as terribly likely to lead to insight. Also my

Re: Library conventions

2000-06-23 Thread Jon Fairbairn
Lennart Augustsson wrote: Frank Atanassow wrote: 2) The Prelude doesn't use it. Well, it doesn't for historical reasons. Am I alone in thinking that the prelude is desperately in need of restructuring? Has anyone got any proposals for nested modules (so we could have

Re: Inferring types

2000-09-08 Thread Jon Fairbairn
If you define `p' as a syntactic function, e.g. p x y = x + y or p x = (+) x rather than via p = (+) then the monomorphism restriction does not apply, and so the type inferred for `p' will be the correct polymorphic type `Num a = a - a - a'. May I just take

Re: old easter egg

2000-12-01 Thread Jon Fairbairn
On Fri, 1 Dec 2000, Zhanyong Wan wrote: Ronald Kuwawi wrote: open text editor, type hash :: [Char] - Int hash = (foldl (+) 0) . (map ord) hash "HASKELL%98" hash "Haskell Ninety Eight !!" surely? -- Jón Fairbairn [EMAIL PROTECTED]

RE: Combinator library gets software prize

2001-01-22 Thread Jon Fairbairn
On Sun, 21 Jan 2001, David Bakin wrote: This article is very good, and having read the conference paper earlier in the year I finished it with only one question: What's a 'quant' ... and is it good or bad to be one? "Ten years ago, Jean-Marc Eber, then a quant at Socit Gnrale,

Re: Notation question

2001-05-29 Thread Jon Fairbairn
and not just type systems but also other aspects of operational semantics. What we have here is a single rule from a rule-based inductive definition of a certain relation G |- s :: S between typing environments G, expressions s and types S. It's probably worth mentioning here that this

foldl'

2001-07-28 Thread Jon Fairbairn
Unless I'm mistaken, foldl' (the strict version of foldl) doesn't appear in (the export list of) the standard prelude or the list library. Is there a good reason for this? New users quite quickly find that they need it. Jón -- Jón Fairbairn [EMAIL PROTECTED]

Re: series

2001-08-15 Thread Jon Fairbairn
hello, i just want to ask a simple question: does somebody have or knowwhere to find a haskell program that calculates the number e, that is the list of infinite digits? It's a nice problem, which I encountered many years ago as one of the first examples I saw of lazy

Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-18 Thread Jon Fairbairn
On Tuesday 16 October 2001 07:29, Fergus Henderson wrote: [...] The whole idea of letting you omit method definitions for methods with no default and having calls to such methods be run-time errors is IMHO exceedingly odd in a supposedly strongly typed language, and IMHO ought to be

Re: Transmitting parameters

2001-11-02 Thread Jon Fairbairn
At 2001-11-01 22:10, raul sierra alcocer wrote: What mechanism of transmiting parameters does Haskell implement? By value. Yes, though one might equally say that they are passed by reference, since in g = let f x = x+x z = factorial 1000 in f z * z the 'first' instance of x

Re: read-ing scientific notation

2001-10-14 Thread Jon Fairbairn
The lexical syntax says that 10e3 means 10 e3 (i.e. two lexemes). I don't like this choice, and it could be fixed in the Revised H98 report. What is the likelihood of anyone *intentionally* writing an integer abutted directly with a varid, followed directly by another

Re: n+k patterns

2002-01-30 Thread Jon Fairbairn
I argued that (Num a, Ord a) makes most sense to me. You argued that (Integral a) was a conscious choice (something I don't remember but I'm sure you're right), and is the right one anyway. I'd be interested to know what others think. If there's any doubt, we'll stay with Integral.

Re: Why is this function type-correct

2002-03-04 Thread Jon Fairbairn
Rijk J. C. van Haaften [EMAIL PROTECTED] wrote: Recently, I wrote a function similar to x :: a x = x 42 which is type-correct (Hugs, Ghc, THIH). Still, from the expression it is clear that the type shoud have a function type. The definition x :: a - b x = x 42 is equally well

Standard Library report: List union

2002-03-04 Thread Jon Fairbairn
The current library report defines unionBy like this: unionBy eq xs ys = xs ++ deleteFirstsBy eq (nubBy eq ys) xs why does it take the nub of ys, but not xs? I'd have expected unionBy eq xs ys = (nubBy eq xs) ++ deleteFirstsBy eq (nubBy eq ys) xs Jón -- Jón Fairbairn

Re: Standard Library report: List union

2002-03-17 Thread Jon Fairbairn
There's a remark at the beginning of 7.2 that says: delete, (\\), union and intersect preserve the invariant=20 that lists don't contain duplicates, provided that=20 their first argument contains no duplicates. The same applies to unionBy etc. This design is one you might reasonably

Re: using less stack

2002-03-18 Thread Jon Fairbairn
Apologies for the typo: that should have been 5 elements, not 500. Amanda Clare wrote: I have stack problems: my program uses too much stack. I suspect, from removing bits of code, that it's due to a foldr in my program. If I use foldr or foldl on a long list (eg 500 bulky

Re: finding ....

2002-03-20 Thread Jon Fairbairn
Could someone post an example of the creation of a temporary file where race conditions are important? /any/ programme that does this on a multi-process system. Between the test for existence and the creation, some other process could have created a file of the same name. Then the create

Re: using less stack

2002-03-20 Thread Jon Fairbairn
Thanks for all the advice. In the end, I couldn't make $! work for me (it always seems to be harder than I think it will be to use it, and $! and deepSeq makes my code run slowly). :-( But a continuation passing style foldl worked wonderfully. As Jay Cox pointed out by email, my answer

Re: finding ....

2002-03-20 Thread Jon Fairbairn
On Wed, Mar 20, 2002, Jon Fairbairn wrote: Could someone post an example of the creation of a temporary file where race conditions are important? /any/ programme that does this on a multi-process system. Occasionally, the presence or absence of a file (usually empty) of a certain

Re: and do notation

2002-03-29 Thread Jon Fairbairn
Wolfgang Jeltsch [EMAIL PROTECTED] wrote: It shouldn't be syntactic suger but at most an operator which does not belong to the monad class. One could define () just as an ordinary function instead of a class member. That sounds to me like the best idea so far. If (as a human reader of a

Re: and do notation

2002-04-02 Thread Jon Fairbairn
On Tue, 2 Apr 2002 10:00:37 +0200 (MET DST), John Hughes [EMAIL PROTECTED] wrote: If (as a human reader of a programme) I see do a - thing1 expression and I notice (perhaps after some modifications) that a is not present in expression, then I

Re: Dependent Types

2002-05-16 Thread Jon Fairbairn
Dominic Steinitz [EMAIL PROTECTED] wrote: I've managed to crack something that always annoyed me when I used to do network programming. [. . .] Suppose I want to send an ICMP packet. The first byte is the type and the second byte is the code. Furthermore, the code depends on the type. Now

fold on Monad?

2002-05-29 Thread Jon Fairbairn
Suppose I have a task I want to do to each line of a file, accumulate a result and output it, I can write main = do stuff - getContents print $ foldl process_line initial_value (lines stuff) ie, it's obviously a fold I can't see a way of doing the same thing directly on the

IO and fold (was Re: fold on Monad? )

2002-05-29 Thread Jon Fairbairn
foldr, foldM, etc. derive a recursive computation from the recursive structure of an input list, so you have to feed one in. If you want to bypass the list, you could use IO-observations (getLine, isEOF) instead of list observations (head/tail, null): Yes you can define it, I should have

Re: [Fwd: F#]

2002-05-30 Thread Jon Fairbairn
Hey Simon et al at Micro$oft, when will there be an H#? But H# is C! we don't want that, surely? :-) Jón -- Jón Fairbairn [EMAIL PROTECTED] 31 Chalmers Road [EMAIL PROTECTED] Cambridge CB1 3SZ+44 1223

Re: layout rule infelicity

2002-05-30 Thread Jon Fairbairn
I like layout but I think the existing rules are too complicated. Unfortunat ely it's difficult to do anything with them without breaking vast swathes of existing code, so we'll just have to put up with them. Well, there's two things to consider: Haskell 98, which probably shouldn't change,

Re: IO and fold (was Re: fold on Monad? )

2002-05-30 Thread Jon Fairbairn
Yes you can define it, And you can, as well. Man sollte sich nicht darauf verlassen, daß ein Englander man verwendet, wenn es angebraucht wäre¹. That's how common idioms come into being; there's no special magic about the folds already in existence. Well, my point is that there is --

Re: layout rule infelicity

2002-05-30 Thread Jon Fairbairn
I wrote: Can someone remind me why the A close brace is also inserted whenever the syntactic category containing the layout list ends part of the rule is there? Lennart wrote: It's so you can write let x = 2+2 in x*x (and similar things) and Arjan van IJzendoorn wrote: x = (3,

Re: FW: Haskell accumulator

2002-06-14 Thread Jon Fairbairn
Paul Graham is collecting canonical accumulator generators at http://www.paulgraham.com/accgen.html , and has Dylan, E, JavaScript, various dialects Lisp, Lua, Rebol, Ruby, Perl, Python and Smalltalk. As others have implied, the only correct answer to this is it's the wrong question. One of

Re: Library report, monad zero laws

2002-06-21 Thread Jon Fairbairn
On Fri, Jun 21, 2002 at 12:50:21PM +0100, Simon Peyton-Jones wrote: | From: Jon Fairbairn [mailto:[EMAIL PROTECTED]] | Sent: 20 June 2002 16:27 | To: Simon Peyton-Jones | Subject: Library report, monad zero laws | | The old report used to include | | m zero = zero | zero

Re: Library report, monad zero laws

2002-06-21 Thread Jon Fairbairn
Apologies for responding to messages in reverse order . . . * My reluctance to change the draft H98 report is rising sharply. Understood! * I don't think the H98 report has ever had laws about mzero etc. No, they went on the transition from 1.4, I think. * And the whole laws business is

Re: Overloading and Literal Numerics

2002-06-27 Thread Jon Fairbairn
Hi, I am trying to create an overloaded function à la Java to be able to call it either with a string or a number. Ex : definePort http definePort 80 but I have problem with restrictions in Haskell's type system Is there a better solution ? If we knew /why/ you wanted to do this we

Re: Overloading and Literal Numerics

2002-06-27 Thread Jon Fairbairn
Alain Cremieux wrote: I am trying to build a functional firewall generator. The first part describes the available protections (kernel, anti-address spoofing, etc.). The second desribes every protocol, and the necessary rules if the corresponding service is enabled (e.g. open the http

Re: forall quantifier

2003-06-06 Thread Jon Fairbairn
On 2003-06-06 at 08:15BST Simon Peyton-Jones wrote: I forget whether I've aired this on the list, but I'm seriously thinking that we should change 'forall' to 'exists' in existential data constructors like this one. You did mention it, and there were several replies. I'd characterise them as

Re: for all quantifier

2003-06-09 Thread Jon Fairbairn
On 2003-06-08 at 18:03PDT Ashley Yakeley wrote: In article [EMAIL PROTECTED], [EMAIL PROTECTED] (Peter G. Hancock) wrote: Thanks! It made me wonder what colour the sky is on planet Haskell. From a Curry-Howard point of view, (I think) the quantifiers are currently the wrong way round.

Search by type (Re: In search of: [a-b] - a - [b])

2003-06-18 Thread Jon Fairbairn
On 2003-06-17 at 20:15EDT Derek Elkins wrote: The closest function I see is ap :: Monad m = m (a - b) - m a - m b (so you could write your function as f fs a = ap fs (return a) not that I would recommend it). Also you may want to check out the Haskell reference at zvon.org, it's indexed by

Re: How overload operator in Haskell?

2003-07-12 Thread Jon Fairbairn
On 2003-07-12 at 20:20+1000 Andrew J Bromage wrote: G'day all. On Fri, Jul 11, 2003 at 04:28:19PM -0400, Dylan Thurston wrote: Don't be silly [...] Never! Or only sometimes. I'm surprised that no-one has yet answered the question How overload operator in Haskell? with Overload operator

Re: User-Defined Operators, Re: Function composition and currying

2003-07-17 Thread Jon Fairbairn
On 2003-07-17 at 09:08+0200 Johannes Waldmann wrote: On Wed, 16 Jul 2003, K. Fritz Ruehr wrote: I think the cutest way to get what you want here is to define a new ^^ operator as follows: (.) = (.) . (.) Indeed this is cute - but let me add a general comment

Re: Laziness

2003-08-02 Thread Jon Fairbairn
On 2003-08-02 at 14:36PDT Dominic Steinitz wrote: Could someone explain to me why this doesn't work test l = hs where hs = map (\x - [x]) [0..abs(l `div` hLen)] hLen = length $ head hs whereas this does test l = hs where hs = map (\x

Re: Haskell for non-Haskell's sake

2003-08-30 Thread Jon Fairbairn
On 2003-08-29 at 17:39PDT Hal Daume III wrote: Hi fellow Haskellers, I'm attempting to get a sense of the topology of the Haskell community. Based on the Haskell Communities Activities reports, it seems that the large majority of people use Haskell for Haskell's sake. If you use Haskell

Re: lifting functions to tuples?

2003-11-18 Thread Jon Fairbairn
On 2003-11-18 at 10:46EST Abraham Egnor wrote: The classic way to write a lift function for tuples is, of course: liftTup f (a, b) = (f a, f b) which has a type of (a - b) - (a, a) - (b, b). I've been wondering if it would be possible to write a function that doesn't require the types in

Re: [Haskell] topology in Haskell

2004-06-10 Thread Jon Fairbairn
On 2004-06-10 at 10:39BST Martin Escardo wrote: Dear Haskell-list members, This is to advertise the monograph Synthetic topology of data types and classical spaces, to appear in ENTCS 87, 150pp, three parts, 6+5+2 chapters. Interesting. But why do you use Int rather than the Integer? In

Re: [Haskell] different element

2004-10-06 Thread Jon Fairbairn
On 2004-10-06 at 10:37CDT ldou wrote: In the random selection, it perhaps select the same element of the string, how can I select two different elements? Consider the \\ operator. -- Jón Fairbairn [EMAIL PROTECTED]

Re: [Haskell] xemacs haskell major mode

2005-01-25 Thread Jon Fairbairn
On 2005-01-24 at 16:32MST Surendra Singhi wrote: Is there any ilisp or slime like package for haskell, which integrates haskell with xemacs or emacs and provides a kind of integrated development environment? I am using Hugs 98. Does URL:

Re: [Haskell] Type of y f = f . f

2005-02-28 Thread Jon Fairbairn
On 2005-02-28 at 18:03GMT Ben Rudiak-Gould wrote: Pedro Vasconcelos wrote: Jim Apple [EMAIL PROTECTED] wrote: Is there a type we can give to y f = f . f y id y head y fst are all typeable? Using ghci: Prelude let y f = f.f Prelude :t y y :: forall c. (c - c) -

Re: [Haskell] Re: Type of y f = f . f

2005-03-01 Thread Jon Fairbairn
On 2005-02-28 at 23:10EST Jim Apple wrote: Jon Fairbairn wrote: If you allow quantification over higher kinds, you can do something like this: d f = f . f d:: a::*, b::**.(b a a) b (b a) a What's the problem with d :: (forall c . b c - c) - b (b a) - a d f = f . f

[Haskell] How to make Haskell more popular

2005-04-01 Thread Jon Fairbairn
1) If another language has a feature, add it to Haskell, so that absolutely everything can be done in more than one way. This allows people to write Haskell programmes without going through the tiresome process of learning Haskell.` 2) Overload the syntax so that the Hamming

Re: [Haskell] offside rule question

2005-07-15 Thread Jon Fairbairn
On 2005-07-15 at 10:49+0200 Tomasz Zielonka wrote: But you can format it this way: let a very long definition of a = and the body has to be here is a very long application to and but using long arguments like definition is not that bad in or let a very long definition

Re: [Haskell] Newbie quick questions

2005-10-04 Thread Jon Fairbairn
On 2005-10-04 at 00:01EDT Mike Crowe wrote: Hi folks, I ran across Haskell at the Great Win32 Computer Language Shootout. A friend approached me with a potential large application to develop. The idea of a language which can reduce time to design and make better code is very

Re: [Haskell] Making Haskell more open

2005-11-14 Thread Jon Fairbairn
On 2005-11-14 at 11:13+0100 Wolfgang Jeltsch wrote: Maybe I changed Konqueror's font settings already. The point is that my settings are in such a way that text with the default font size is well readable while not taking up too much space. The problem is with haskell.org's links. They

Re: [Haskell] Fonts on haskell.org

2005-11-14 Thread Jon Fairbairn
On 2005-11-14 at 10:38EST John Peterson wrote: If someone sends me a new css file I'll be happy to throw it on haskell.org for you. Please send an email to this list if you want to do this so nobody else wastes their time. Is anything more needed than the attached patch? If so, I'm willing

Re: [Haskell] Re: Haskell Weekly News: March 13, 2006

2006-03-17 Thread Jon Fairbairn
On 2006-03-17 at 06:58GMT Aaron Denney wrote: On 2006-03-17, Donald Bruce Stewart [EMAIL PROTECTED] wrote: Well, there is a way -- it's fairly easy with the right regex -- but is it really ambiguous? Do people find it confusing? What do other sites do? Why not the ISO standard -MM-DD?

Re: [Haskell] installing streams library

2006-05-20 Thread Jon Fairbairn
On 2006-05-20 at 12:00+0200 Sebastian Sylvan wrote: A quick sales pitch: usually you, the library user, can just type: ./runhaskell Setup.hs configure ./runhaskell Setup.hs build ./runhaskell Setup.hs install And it will Do The Right Thing(TM), which is nice. This is something I've never

Re: [Haskell] installing streams library

2006-05-20 Thread Jon Fairbairn
On 2006-05-20 at 11:58EDT Robert Dockins wrote: On Saturday 20 May 2006 06:53 am, Jon Fairbairn wrote: Make allows one to set up rules about what depends on what, so why can't we just arrange it so that someone who wants to install the thing just hast to type ./runhaskell Setup.hs

Re: [Haskell] Haskell web forum

2006-09-20 Thread Jon Fairbairn
On 2006-09-20 at 21:19+0200 Niklas Broberg wrote: A mailing list will never be enough. Really? A forum has way way more potential. More potential than what we have already: URL: http://dir.gmane.org/gmane.comp.lang.haskell.general ? Jón -- Jón Fairbairn

  1   2   3   4   >