Re: [Haskell-cafe] Justification for Ord inheriting from Eq?

2006-04-06 Thread Brian Hulley
John Meacham wrote: On Thu, Apr 06, 2006 at 10:52:52PM +0100, Brian Hulley wrote: [snip] The problem of allowing classes (in Haskell) to inherit is that you end up with heirarchies which fix the design according to some criteria which may later turn out to be invalid, whereas if there were

Re: [Haskell-cafe] Justification for Ord inheriting from Eq?

2006-04-06 Thread Brian Hulley
Brian Hulley wrote: John Meacham wrote: [snip] 1. one really does logically derive from the other, Eq and Ord are like this, the rules of Eq says it must be an equivalance relation and that Ord defines a total order over that equivalance relation. this is a good thing, as it lets you write code

Re: [Haskell-cafe] show for functional types

2006-04-05 Thread Brian Hulley
Robert Dockins wrote: On Apr 1, 2006, at 3:23 PM, Brian Hulley wrote: [snip] For particular types T1 and T2, if (f (x::T1))::T2 === g x for all x in T1 then f :: T1-T2 and g ::T1-T2 can be freely substituted since the context T1-T2 cannot tell them apart. Having thought about this a bit more

Re: [Haskell-cafe] show for functional types

2006-04-01 Thread Brian Hulley
Claus Reinke wrote: the usual way to achieve this uses the overloading of Nums in Haskell: when you write '1' or '1+2', the meaning of those expressions depends on their types. in particular, the example above uses 'T Double', not just 'Double'. However there is nothing in the functions

Re: [Haskell-cafe] show for functional types

2006-04-01 Thread Brian Hulley
Brian Hulley wrote: (==) (Add xs) (Add ys) = and (map (\(x, y) - x==y) (zip xs ys)) What on earth was I thinking!!! ;-) Should be: (==) (Add xs) (Add ys) = xs == ys (Doesn't affect the validity of my argument though...) ___ Haskell-Cafe

Re: [Haskell-cafe] show for functional types

2006-04-01 Thread Brian Hulley
Robert Dockins wrote: On Saturday 01 April 2006 11:53 am, Brian Hulley wrote: Claus Reinke wrote: the usual way to achieve this uses the overloading of Nums in Haskell: when you write '1' or '1+2', the meaning of those expressions depends on their types. in particular, the example above uses

Re: [Haskell-cafe] show for functional types

2006-04-01 Thread Brian Hulley
Robert Dockins wrote: [snip] From an earlier post: Now since f and g compute the same results for the same inputs, anywhere in a program that you can use f you could just replace f by g and the observable behaviour of the program would be completely unaffected. This is what referential

Re: [Haskell-cafe] show for functional types

2006-04-01 Thread Brian Hulley
Claus Reinke wrote: [snip] ... (try this for one study of the many definitions [scanned paper - 3MB]: http://www.dina.kvl.dk/~sestoft/papers/SondergaardSestoft1990.pdf ). Thanks for the link, Regards, Brian. ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] show for functional types

2006-03-31 Thread Brian Hulley
Greg Buchholz wrote: Neil Mitchell wrote: Now lets define super show which takes a function, and prints its code behind it, so: superShow f = not superShow g = \x - case ... now superShow f /= superShow g, so they are no longer referentially transparent. OK. I'm probably being really

[Haskell-cafe] Wrapping the IO monad to get safe, self-describing imperative APIs

2006-03-30 Thread Brian Hulley
Hi - In a discussion started on the GHC mailing list http://www.haskell.org//pipermail/glasgow-haskell-users/2006-March/009923.html I discovered an idea for typing imperative API functions that may be of interest to other people, and which makes use of Haskell's type system to achieve a level

Re: Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-29 Thread Brian Hulley
Robin Green wrote: On Wed, 29 Mar 2006 12:50:02 +0100 Jon Fairbairn [EMAIL PROTECTED] wrote: [snip] 1) choosing the optimal reduction strategy is undecidable 2) we shouldn't (in general) attempt to do undecidable things automatically [snip] [snip] I suggest that a Haskell program should be

Re: Pragmatic concurrency Re: [Haskell-cafe] multiple computations, same input

2006-03-29 Thread Brian Hulley
Brian Hulley wrote: Robin Green wrote: On Wed, 29 Mar 2006 12:50:02 +0100 Jon Fairbairn [EMAIL PROTECTED] wrote: [snip] 1) choosing the optimal reduction strategy is undecidable 2) we shouldn't (in general) attempt to do undecidable things automatically [snip] [snip] I suggest

Re: [Haskell-cafe] Re: how would this be done? type classes?existentialtypes?

2006-03-23 Thread Brian Hulley
Ben Rudiak-Gould wrote: Brian Hulley wrote: Is there a reason for using instead of [exists a. Resource a=a] ? Only that = looks like a function arrow, looks like a tuple. I stole this notation from an unpublished paper by SimonPJ et al on adding existential quantification to Haskell

Re: [Haskell-cafe] Re: Question regarding let clauses

2006-03-09 Thread Brian Hulley
Christian Maeder wrote: Martin Percossi wrote: matMul a b = do { let foo = 2*5; return a } probably { let {foo = 2*5}; return a } will work (untested) your ; indicates a further let-equation, but the possibility to use ; without { and } is a bit pathologic (and haddock used to reject

[Haskell-cafe] Re: MUA written in Haskell (was: Getting GHC to print Done when it's finished linking?)

2006-03-08 Thread Brian Hulley
Nils Anders Danielsson wrote: On Tue, 07 Mar 2006, Brian Hulley [EMAIL PROTECTED] wrote: (Moved from ghc-users.) Brian Hulley wrote: (time for a proper email client to be written in Haskell! ;-) ) I had the same thought yesterday, after an Emacs-Lisp session in which I was trying to get

Re: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-07 Thread Brian Hulley
Brian Hulley wrote: translate :: (Monad m) = String - m String translate = do createParseContext readToFirstIdentifier dealWithDeclarator consolidateOutput The type signature above doesn't match the do

Re: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-07 Thread Brian Hulley
Shannon -jj Behrens wrote: I did think of using a monad, but being relatively new to Haskell, I was confused about a few things. Let's start by looking at one of my simpler functions: -- Keep pushing tokens until we hit an identifier. pushUntilIdentifier :: ParseContextTransformation

Re: [Haskell-cafe] Layout rule (was Re: PrefixMap: code reviewrequest)

2006-03-06 Thread Brian Hulley
Malcolm Wallace wrote: Brian Hulley wrote: However I think there is an error in the description of this in section 2.7 of the Haskell98 report, which states: If the indentation of the non-brace lexeme immediately following a where, let, do or of is less than or equal to the current

Re: [Haskell-cafe] Comparing programs

2006-03-06 Thread Brian Hulley
Harry Chesley wrote: But here's the thing that makes it hard (at least for me): two programs are considered the same if they can be made to match by rearranging the order of the input parameters. I.e., f(a), g(b) is the same as f(b), g(a). Although parameters can be reordered, they cannot be

Re: [Haskell-cafe] | vs. $ (was: request for code review)

2006-03-06 Thread Brian Hulley
Shannon -jj Behrens wrote: I find ctx | currTok | tokenType to be more readable than tokenType $ currTok $ ctx because you're not reading the code in reverse. That's my primary complaint with . and $. That's especially the case when I'm spreading the code over multiple lines: -- Translate a C

Re: [Haskell-cafe] request for code review

2006-03-05 Thread Brian Hulley
Neil Mitchell wrote: stackTop ctx = let (x:xs) = stack ctx in x stackTop ctx = head ctx stackTop ParseContext{stack=x:_} = x or: stackTop ctx = head (stack ctx) ===stackTop ctx = head . stack $ ctx ===stackTop = head . stack Regards, Brian.

Re: [Haskell-cafe] Layout rule (was Re: PrefixMap: code reviewrequest)

2006-03-04 Thread Brian Hulley
Daniel Fischer wrote: Am Freitag, 3. März 2006 19:21 schrieb Brian Hulley: Brian Hulley wrote: Brian Hulley wrote: [snip] AFAICT, the description in the report is correct, *except for the 'where' in module LayOut where*. [snip] So my guess is that layout-processing is applied only

Re: [Haskell-cafe] Layout rule (was Re: PrefixMap: code reviewrequest)

2006-03-03 Thread Brian Hulley
Brian Hulley wrote: Brian Hulley wrote: One other thing I've been wanting to ask (not to change! :-)) for a while is: how is the following acceptable according to the rules in the Haskell98 report where where is one of the lexemes, which when followed by a line more indented than the line

Re: [Haskell-cafe] Layout rule (was Re: PrefixMap: code reviewrequest)

2006-03-02 Thread Brian Hulley
Brian Hulley wrote: [snip] So any solutions welcome :-) Thank to everyone who replied to my queries about this whole layout issue. One other thing I've been wanting to ask (not to change! :-)) for a while is: how is the following acceptable according to the rules in the Haskell98 report

Re: [Haskell-cafe] Layout rule (was Re: PrefixMap: code reviewrequest)

2006-03-01 Thread Brian Hulley
Benjamin Franksen wrote: [snip] I am used to hitting TAB key and get the correct number of spaces, according to how I configured my editor (NEdit) for the current language mode. The only thing then is what happens when you type backspace or left arrow to get back out to a previous

Re: [Haskell-cafe] Re: PrefixMap: code review request

2006-02-28 Thread Brian Hulley
Ben Rudiak-Gould wrote: Brian Hulley wrote: Whoever thought up the original Haskell layout rule assumed that people would be happy using a single fixed width font, tabs set to 8 spaces, and didn't care about the brittleness of the code (in the face of identifier renamings) it allowed one

Re: [Haskell-cafe] Layout rule (was Re: PrefixMap: code review request)

2006-02-28 Thread Brian Hulley
Ben Rudiak-Gould wrote: Brian Hulley wrote: Here is my proposed layout rule: 1) All layout keywords (where, of, let, do) must either be followed by a single element of the corresponding block type, and explicit block introduced by '{', or a layout block whose first line starts on the *next

Re: [Haskell-cafe] PrefixMap: code review request

2006-02-27 Thread Brian Hulley
David F.Place wrote: [snip] partList :: Ord k = [([k],v)]-[k]-[(k,[([k],v)])] partList pairs alphabet = reverse . fst $ foldl' f ([],pairs) alphabet where f (result,pairs) l = (result',rest) where (part,rest) = span ((==l) . head . fst) pairs result' = if null part

Re: [Haskell-cafe] PrefixMap: code review request

2006-02-27 Thread Brian Hulley
David F. Place wrote: On Feb 27, 2006, at 5:54 PM, Brian Hulley wrote: there is a parse error (using ghc) at the line beginning with result'. This binding doesn't line up with anything. Also the second 'where' is dangerously close to the column started by the 'f' after the first 'where' (may

Re: [Haskell-cafe] rounding errors with real numbers.

2006-02-26 Thread Brian Hulley
Matthias Fischmann wrote: | -- fix rounding error: | repair [i] = [upper] | repair (h:t) = h : repair t Just to point out that this only fixes the last element of the list, so inputs like [1,2,10.8,10.8] would not be handled properly if you require the same input values to map to

[Haskell-cafe] Context in data and class declarations (was haskell programming guidelines)

2006-02-25 Thread Brian Hulley
Hi - In http://www.informatik.uni-bremen.de/agbkb/forschung/formal_methods/CoFI/hets/src-distribution/versions/HetCATS/docs/Programming-Guidelines.txt one of the recommendations states: Don't put class constraints on a data type, constraints belong only to the functions that manipulate the

Re: [Haskell-cafe] Context in data and class declarations (was haskellprogramming guidelines)

2006-02-25 Thread Brian Hulley
Brian Hulley wrote: snip Another confusing thing is the use of the word inheritance in tutorials/books about class declarations. Unlike object oriented languages, where a class or interface gets all the methods of its ancestor classes/interfaces in addition to some new methods declared

Re: [Haskell-cafe] Type inference

2006-02-09 Thread Brian Hulley
Cale Gibbard wrote: On 09/02/06, Brian Hulley [EMAIL PROTECTED] wrote: Brian Hulley wrote: f :: forall m. (forall a. a-m a) - c - d - (m c, m d) Of course this type doesn't work on your original example, since (,) is a type constructor with two parameters, not one, but this type signature

Re: [Haskell-cafe] Type inference

2006-02-08 Thread Brian Hulley
Fred Hosch wrote: Is type inferencing in Haskell essentially the same as in SML? Thanks. Well, that depends on what you mean by essentially the same ;-) Both languages are based on the same Hindley-Milner type inference algorithm, so both suffer from the same problem that a function such as

Re: [Haskell-cafe] Type inference

2006-02-08 Thread Brian Hulley
Cale Gibbard wrote: On 08/02/06, Brian Hulley [EMAIL PROTECTED] wrote: Fred Hosch wrote: Is type inferencing in Haskell essentially the same as in SML? Thanks. Well, that depends on what you mean by essentially the same ;-) Both languages are based on the same Hindley-Milner type inference

Re: [Haskell-cafe] Type inference

2006-02-08 Thread Brian Hulley
Brian Hulley wrote: f :: (forall a m. a - m a) - c - d - (m c, m d) The above is wrong - there is no way to quantify m properly. This must be why intersection types need to be written with after all ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Type inference

2006-02-08 Thread Brian Hulley
Brian Hulley wrote: Brian Hulley wrote: f :: (forall a m. a - m a) - c - d - (m c, m d) The above is wrong - there is no way to quantify m properly. This must be why intersection types need to be written with after all What am I saying! It's right after all, and might

Re: [Haskell-cafe] Type inference

2006-02-08 Thread Brian Hulley
Brian Hulley wrote: Brian Hulley wrote: Brian Hulley wrote: f :: (forall a m. a - m a) - c - d - (m c, m d) The above is wrong - there is no way to quantify m properly. This must be why intersection types need to be written with after all What am I saying! It's right after

Re: [Haskell-cafe] Re: extending bang proposal Re: strict Haskelldialect

2006-02-07 Thread Brian Hulley
Ben Rudiak-Gould wrote: Brian Hulley wrote: One motivation seems to be that in the absence of whole program optimization, the strictness annotations on a function's type can allow the compiler to avoid creating thunks at the call site for cross-module calls whereas using seq in the function

Re: [Haskell-cafe] Re: extending bang proposal Re: strict Haskelldialect

2006-02-06 Thread Brian Hulley
Ben Rudiak-Gould wrote: As Robert Dockins said, it's not implemented, and it isn't clear how to implement it. At this point it's looking fairly likely that my PhD thesis will be on this very topic, so stay tuned. Isn't all this already implemented in Clean? Regards, Brian.

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-05 Thread Brian Hulley
Jon Fairbairn wrote: Brian Hulley wrote: snip Not exactly alone; I've felt it was wrong ever since we argued about it for the first version of Haskell. : for typing is closer to common mathematical notation. But it's far too late to change it now. - it's just syntax after all Well I'm

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-05 Thread Brian Hulley
Tomasz Zielonka wrote: The only problem I see right now is related to change locality. If I have a chain like this: f x y . g x $ z and I want to add some transformation between g and z I have to change one line and insert another f x y . g x . h x y $ z With

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-05 Thread Brian Hulley
Tomasz Zielonka wrote: On Sun, Feb 05, 2006 at 01:14:42PM -, Brian Hulley wrote: How about: f x y . g x $ z then you only need to add the line . h x y But then you have a problem when you when you want to add something at the beginning ;-) With right-assoc $ adding

Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-05 Thread Brian Hulley
Brian Hulley wrote: Brian Hulley wrote: Robin Green wrote: snip So simply make strictness the default and have laziness annotations (for arguments), instead of making laziness the default and having strictness annotations. Where would you put these laziness annotations? If you put them

Re: Re[2]: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-05 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Brian, Saturday, February 04, 2006, 4:50:44 AM, you wrote: One question is how to get some kind of do notation that would work well in a strict setting. The existing do notation makes use of lazyness in so far as the second arg of is only evaluated when needed.

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-05 Thread Brian Hulley
Tomasz Zielonka wrote: On Sun, Feb 05, 2006 at 01:10:24PM -, Brian Hulley wrote: 2) Use , instead of ; in the block syntax so that all brace blocks can be replaced by layout if desired (including record blocks) Wouldn't it be better to use ; instead of , also for record syntax? I

Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-05 Thread Brian Hulley
Tomasz Zielonka wrote: On Sun, Feb 05, 2006 at 05:18:55PM -, Brian Hulley wrote: I must admit I'm a bit confused as to why the strictness annotations in Haskell (and Clean) are only allowed in data declarations and not function declarations Clean does allow strictness annotations

Re: [Haskell-cafe] Re: Why is $ right associative insteadofleftassociative?

2006-02-05 Thread Brian Hulley
Ben Rudiak-Gould wrote: Paul Hudak wrote: Minor point, perhaps, but I should mention that : is not special syntax -- it is a perfectly valid infix constructor. snip ... but no more confusing than the fact that [f x | x - xs] is not the same as (map f xs). Can you explain why? On page 258

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-05 Thread Brian Hulley
Tomasz Zielonka wrote: On Sun, Feb 05, 2006 at 04:36:44PM -, Brian Hulley wrote: Just in case you are interested, in the preprocessor I'm writing, I would write these examples as: (.) # f x y g x h x y $ z

[Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread Brian Hulley
Hi - In the Haskell98 report section 4.4.2 $ is specified as being right associative. This means that f $ a0 a1 $ b0 b1 would parse as f (a0 a1 (b0 b1)) which seems rather strange to me. Surely it would be much more useful if $ were defined as left associative so that it could be used to

Re: [Haskell-cafe] Why is $ right associative instead of left associative?

2006-02-04 Thread Brian Hulley
Tomasz Zielonka wrote: On Sat, Feb 04, 2006 at 02:52:20PM -, Brian Hulley wrote: Hi - In the Haskell98 report section 4.4.2 $ is specified as being right associative. This means that f $ a0 a1 $ b0 b1 would parse as f (a0 a1 (b0 b1)) which seems rather strange to me. Surely it would be much

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Brian Hulley
Brian Hulley wrote: Tomasz Zielonka wrote: On Sat, Feb 04, 2006 at 02:52:20PM -, Brian Hulley wrote: Hi - In the Haskell98 report section 4.4.2 $ is specified as being right associative. This means that f $ a0 a1 $ b0 b1 would parse as f (a0 a1 (b0 b1)) which seems rather strange to me

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Brian Hulley
Tomasz Zielonka wrote: On Sat, Feb 04, 2006 at 07:15:47PM -, Brian Hulley wrote: I think the mystery surrounding :: and : might have been that originally people thought type annotations would hardly ever be needed whereas list cons is often needed, but now that it is regarded as good

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Brian Hulley
Stefan Holdermans wrote: -BEGIN PGP SIGNED MESSAGE- Hash: SHA1 Brian wrote: I think the mystery surrounding :: and : might have been that originally people thought type annotations would hardly ever be needed whereas list cons is often needed, but now that it is regarded as good

Re: [Haskell-cafe] Why is $ right associative instead of leftassociative?

2006-02-04 Thread Brian Hulley
[EMAIL PROTECTED] wrote: G'day all. Quoting [EMAIL PROTECTED]: This is the way that I normally express it. Partly because I find function application FAR more natural than right-associative application, I meant to say that I find function COMPOSITION more natural than right-associative

Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley
Bulat Ziganshin wrote: Hello Wolfgang, Friday, February 03, 2006, 1:46:56 AM, you wrote: i had one idea, what is somewhat corresponding to this discussion: make a strict Haskell dialect. implement it by translating all expressions of form f x into f $! x and then going to the standard (lazy)

Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley
Jan-Willem Maessen wrote: I pointed out some problems with strict Haskell in a recent talk, but I think it'd be worth underscoring them here in this forum. Is the text of this talk or points raised in it available online anywhere? snip There is one very difficult piece of syntax in a strict

Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley
Robin Green wrote: On Fri, 3 Feb 2006 19:33:12 - Brian Hulley [EMAIL PROTECTED] wrote: I've been thinking along these lines too, because it has always seemed to me that laziness is just a real nuisance because it hides a lot of inefficiency under the carpet as well as making the time/space

Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley
John Meacham wrote: On Fri, Feb 03, 2006 at 07:33:12PM -, Brian Hulley wrote: One question is how to get some kind of do notation that would work well in a strict setting. The existing do notation makes use of lazyness in so far as the second arg of is only evaluated when needed. Perhaps

Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley
Brian Hulley wrote: if' :: ~a - ~b - Bool Oooops :-) if' :: Bool - ~a - ~a - a Regards, Brian. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re[2]: strict Haskell dialect

2006-02-03 Thread Brian Hulley
Brian Hulley wrote: Robin Green wrote: snip So simply make strictness the default and have laziness annotations (for arguments), instead of making laziness the default and having strictness annotations. Where would you put these laziness annotations? If you put them in the function

Re: [Haskell-cafe] Evaluating arithmetic expressions at run time

2006-01-28 Thread Brian Hulley
Andrew Savige wrote: --- Cale Gibbard wrote: Apart from moving to a lookup Map or something, a simple reordering of the arguments allows you to shorten things up a bit: myeval :: String - Int - Int - Int myeval + = (+) myeval - = (-) myeval * = (*) etc. Thanks to all for the excellent

Re: [Haskell-cafe] Evaluating arithmetic expressions at run time

2006-01-28 Thread Brian Hulley
Brian Hulley wrote: eg myeval (+) 1 2 myeval 1 2 (+)-- I *always* seem to make at least one mistake per post ;-) (I originally wrote the code to take the op first, which is the usual Haskell convention so that you can do useful things with (myeval someop) but then I noticed

Re: [Haskell-cafe] unary pattern matching

2006-01-27 Thread Brian Hulley
John Meacham wrote: On Fri, Jan 27, 2006 at 12:28:23PM +1100, Donald Bruce Stewart wrote: john: I have often wanted a shorthand syntax for testing if a value matches a given pattern. I want to implement such an extension for jhc but can't decide an appropriate syntax so I thought I'd ask the

[Haskell-cafe] Another idea for record field selection and better namespace management

2006-01-27 Thread Brian Hulley
Hi - To avoid the problems with so many names being put into a module's namespace, data declarations could implicitly define sub-modules and class/instance declarations as follows: module M where data Foo = FooCon {x : Int} would declare (as seen from inside M) Foo, Foo.FooCon,

Re: [Haskell-cafe] Another idea for record field selection and betternamespace management

2006-01-27 Thread Brian Hulley
Apologies - I've noticed some mistakes corrected as follows: Brian Hulley wrote: class //x a b where x : a - b class //FooCon a b where FooCon : a - b class //x a b | a - b where-- I think this fundep is correct x :: a-b

Re: [Haskell-cafe] Another idea for record field selection and betternamespace management

2006-01-27 Thread Brian Hulley
Another correction... Brian Hulley wrote: data Col1 a = One a data Col2 a = One a | Two a useOne :: ( //One col a) = col - a useOne (One x) = x should be useOne :: (//One a col) = col - a ___ Haskell-Cafe

Re: [Haskell-cafe] Avoiding name collisions by using value spaces instead of modules

2006-01-17 Thread Brian Hulley
Tomasz Zielonka wrote: [A bit late reply - I've just returned from vacation] On Sun, Jan 08, 2006 at 05:47:19PM -, Brian Hulley wrote: All I'm proposing is that the compiler should do all this painful work for you, so that you don't need to bother creating a different file that then needs

Re: [Haskell-cafe] Avoiding name collisions by using value spaces instead of modules

2006-01-17 Thread Brian Hulley
Tomasz Zielonka wrote: On Sun, Jan 08, 2006 at 01:06:18PM -, Brian Hulley wrote: 5) We can get all the advantages of automatic namespace management the OOP programmers take for granted, in functional programming, by using value spaces as the analogue of objects, and can thereby get rid

Re: [Haskell-cafe] Re: What does the Haskell type system do withshow (1+2)?

2006-01-13 Thread Brian Hulley
Cale Gibbard wrote: Snip So long as we're going to have a defaulting mechanism, it seems a bit odd to restrict it to Num, and to classes in the Prelude. Instead of having literals such as 1 that could be Int, Integer, or Float etc, why not just have one Number type declared as something

Re: [Haskell-cafe] Avoiding name collisions by using value spacesinstead of modules

2006-01-10 Thread Brian Hulley
Brian Hulley wrote: Cale Gibbard wrote: Unifying these two under a single operation is certainly trickier, and it's a little more questionable that it should be done at all, given that their types are so different -- below is the closest I could come to it off-hand. snip Thanks! I'm impressed

[Haskell-cafe] Intersection types for Haskell?

2006-01-10 Thread Brian Hulley
a or class Insert t@(h (c a)) c a where -- re-using as-pattern syntax insert :: t - c a - c a to avoid having to have a special syntax just for functional dependencies and/or to be able to write more complicated fundeps more succinctly? Regards, Brian Hulley

Re: [Haskell-cafe] Intersection types for Haskell?

2006-01-10 Thread Brian Hulley
. However this does not seem to be quite so general as intersection types, because it would only allow me to define f for some specific g ie the g of Foo, rather than for any general function... Regards, Brian Hulley ___ Haskell-Cafe mailing list

Re: [Haskell-cafe] Intersection types for Haskell?

2006-01-10 Thread Brian Hulley
Taral wrote: On 1/10/06, Brian Hulley [EMAIL PROTECTED] wrote: Hi - I'm wondering if there is any possiblility of getting intersection types into Haskell. For example, at the moment there is no (proper) typing for: f g x y = (g x, g y) Ideally, I'd like to be able to write: f

Re: [Haskell-cafe] Intersection types for Haskell?

2006-01-10 Thread Brian Hulley
Brian Hulley wrote: Taral wrote: I have no idea what kind of function would have type (a - b c - d). Can you give an example? g x = x because g 3 = 3 so g has type Int - Int but also g 'a' = 'a' so g has type Char - Char hence g has type Int - Int Char - Char Actually I should have said

Re: [Haskell-cafe] Intersection types for Haskell?

2006-01-10 Thread Brian Hulley
Brian Hulley wrote: snip which is perhaps clearer and prevents bad types such as (Int - String Int - Char) by construction. Oops! I forgot that functions with such types can exist via multi-parameter type classes and overloading - this may be one reason why intersection types have not yet

[Haskell-cafe] Avoiding name collisions by using value spaces instead of modules

2006-01-08 Thread Brian Hulley
feedback on these ideas would be welcome. Thanks for reading so far! Brian Hulley PS Everything above is purely intended for resolving the kind of ad-hoc overloading that is not amenable to treatment by type classes (which transforms some subset of the ad-hoc-overloaded functions which share

Re: [Haskell-cafe] Avoiding name collisions by using value spaces instead of modules

2006-01-08 Thread Brian Hulley
- Original Message - From: Daniel Fischer [EMAIL PROTECTED] To: Brian Hulley [EMAIL PROTECTED] Cc: Haskell-cafe haskell-cafe@haskell.org Sent: Sunday, January 08, 2006 3:47 PM Subject: Re: [Haskell-cafe] Avoiding name collisions by using value spaces instead of modules Am Sonntag

Re: [Haskell-cafe] Avoiding name collisions by using value spaces instead of modules

2006-01-08 Thread Brian Hulley
- Original Message - From: Cale Gibbard [EMAIL PROTECTED] To: Brian Hulley [EMAIL PROTECTED] Cc: Daniel Fischer [EMAIL PROTECTED]; Haskell-cafe haskell-cafe@haskell.org Sent: Sunday, January 08, 2006 5:54 PM Subject: Re: [Haskell-cafe] Avoiding name collisions by using value spaces

Re: [Haskell-cafe] Avoiding name collisions by using value spaces instead of modules

2006-01-08 Thread Brian Hulley
Cale Gibbard wrote: snip Thanks for the illustration - I see another advantage with type classes is that you only need to write the type signature once (in the class declaration) instead of before each instance binding. Secondly, if the functions are really different, and you never plan

Re: [Haskell-cafe] Avoiding name collisions by using value spaces instead of modules

2006-01-08 Thread Brian Hulley
Cale Gibbard wrote: Unifying these two under a single operation is certainly trickier, and it's a little more questionable that it should be done at all, given that their types are so different -- below is the closest I could come to it off-hand. --- {-# OPTIONS_GHC -fglasgow-exts #-} -- for

<    1   2   3   4