Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-05 Thread Robert Dockins
On Sat, 2005-03-05 at 00:25 +0100, Benjamin Franksen wrote: OK, I can see now that this makes sense syntactically. Still, it is strange that the class name is handled as if it were a type constructor. Yes. It makes a weird sort of sense if you pretend type classes are actually type

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-05 Thread Keean Schupke
Well it does have some validity, but I am not sure its from category theory... A type is a set of values (constructors): data Type = Constr1 | Constr2 | Constr3 likewise a class is a set of types (IE we lift one level) class Class instance Class Type1 instance Class Type2 instance Class Type3 So

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-04 Thread Benjamin Franksen
On Sunday 20 February 2005 14:19, Keean Schupke wrote: TH has supported multi-parameter classes for a while... new in 6.4 is support for fundeps. Yes, but unfortunately TH cannot create instances for them which is usually the boilerplate you want to avoid. From Language.Haskell.TH: data Dec =

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-04 Thread Lemmih
On Fri, 4 Mar 2005 15:26:52 +0100, Benjamin Franksen [EMAIL PROTECTED] wrote: On Sunday 20 February 2005 14:19, Keean Schupke wrote: TH has supported multi-parameter classes for a while... new in 6.4 is support for fundeps. Yes, but unfortunately TH cannot create instances for them which

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-04 Thread robert dockins
Lemmih wrote: On Fri, 4 Mar 2005 15:26:52 +0100, Benjamin Franksen [EMAIL PROTECTED] wrote: On Sunday 20 February 2005 14:19, Keean Schupke wrote: TH has supported multi-parameter classes for a while... new in 6.4 is support for fundeps. Yes, but unfortunately TH cannot create instances for them

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-04 Thread Keean Schupke
robert dockins wrote: Is that really how this is done? That doesn't seem like it can be right: instance X (a b) -- single parameter class where 'a' has an arrow kind is very different from: instance X a b-- multiple parameter class I would expect a type constructed with 'appT' to correspond

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-04 Thread Benjamin Franksen
On Friday 04 March 2005 16:32, Keean Schupke wrote: robert dockins wrote: Is that really how this is done? That doesn't seem like it can be right: instance X (a b) -- single parameter class where 'a' has an arrow kind is very different from: instance X a b-- multiple parameter

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-04 Thread Benjamin Franksen
On Friday 04 March 2005 23:44, Keean Schupke wrote: Benjamin Franksen wrote: Consider: class Bogus a b instance Bogus Int Char How do you express the /instance/ in TH? Using AppT? That would be: (using 6.4 syntax) AppT (AppT (ConT (mkName Bogus)) (ConT ''Int)) (ConT

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-03 Thread Keean Schupke
Benjamin Franksen wrote: This is extremely cool. The type of unwrap is indeed general enough. Unfortunately, it doesn't help, because the result type of wrap Wrap (forall a. a - a) still isn't accepted in an instance declaration. Neither is the pair (unwrap, Wrap (forall a. a - a)) Or maybe I

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-02 Thread Ben Rudiak-Gould
Benjamin Franksen wrote: On Thursday 24 February 2005 23:27, Keean Schupke wrote: Well, not quite true, because the type of the label is used to index the value, the selection happens at compile time. So at run time there is no instance selection left... it is simply the value. At least in

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-02 Thread Keean Schupke
Ben Rudiak-Gould wrote: It does. An HList of Int,Bool,Char is isomorphic to the type (Int,(Bool,(Char,(, and selecting the Bool element will ultimately compile to code like this: case list of (_,(x,_)) - ... It doesn't need to search for the right element at runtime, and it doesn't

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-28 Thread Benjamin Franksen
On Thursday 24 February 2005 23:27, Keean Schupke wrote: Benjamin Franksen wrote: Well at the moment this would give an error, but remember the list is heterogeneous, so you can just not give the list a type, and simply append the specific function... admitedly this is not as type-safe.

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Benjamin Franksen wrote: On Sunday 20 February 2005 10:16, Daan Leijen wrote: Benjamin Franksen wrote: This library class defines the operations on a record: class RecordField r l t | r l - t where getField :: l - r - t putField :: l - t - r - r I have once written a short

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Keean Schupke wrote: Hmm... actually they can be used on the LHS... {-# OPTIONS -fglasgow-exts #-} module Main where class Test a b | a - b where test :: a - b newtype I = I (forall a . Integral a = a) newtype S = S (forall a . Show a = a) instance Test I Int where test _ = 7

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Benjamin Franksen
On Thursday 24 February 2005 11:56, Keean Schupke wrote: Benjamin Franksen wrote: You mentioned that higher-ranked types are not allowed in instance declarations and that this limits the usefulness of your translation. This is unfortunate and applies to my translation too. From what I read

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Benjamin Franksen wrote: I haven't read Daan's paper yet, but I think his translation is similar to the TIR (type indexed row) part of the HList library... Keean. Dear Keean, you should read more carefully what people write. Nowhere have I stated that I want higher-ranked *labels*. In fact,

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Having looked at the translation on page 10 of Daan's paper, I can see no advantage in this encoding, nor does it look like it supports higher ranked types in any way... (Infact it has the disadvantage of requiring a class per record, whereas the records in the HList paper require only a class

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Benjamin Franksen
On Thursday 24 February 2005 15:01, Keean Schupke wrote: Having looked at the translation on page 10 of Daan's paper, I can see no advantage in this encoding, nor does it look like it supports higher ranked types in any way... (Infact it has the disadvantage of requiring a class per record,

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Benjamin Franksen wrote: Sorry, I jumped to conclusions a bit too fast. I thought one could get rid of the newtype unwrapper if one applied it away. But this is nonsense because one still has the class constraint involving the newtype. It just doesn't work. I still wonder if your TH generated

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Benjamin Franksen
On Thursday 24 February 2005 19:51, Keean Schupke wrote: Benjamin Franksen wrote: I still wonder if your TH generated code can handle higher ranked field types; i.e. can I write $(ttypelift [| data Record = Record { field1 :: Int, field2 :: (forall a. a- a) } |] ) or does ghc

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Benjamin Franksen wrote: Well at the moment this would give an error, but remember the list is heterogeneous, so you can just not give the list a type, and simply append the specific function... admitedly this is not as type-safe. hUpdateAtLabel field2 someFunction myRecord That is an

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-23 Thread Benjamin Franksen
On Sunday 20 February 2005 14:19, Keean Schupke wrote: TH has supported multi-parameter classes for a while... new in 6.4 is support for fundeps. That's mighty cool ;) Is this (TH in general, extensions in particular) documented somewhere? Ben ___

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-23 Thread Benjamin Franksen
On Sunday 20 February 2005 10:16, Daan Leijen wrote: Benjamin Franksen wrote: This library class defines the operations on a record: class RecordField r l t | r l - t where getField :: l - r - t putField :: l - t - r - r I have once written a short note about how

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-20 Thread Daan Leijen
Benjamin Franksen wrote: This library class defines the operations on a record: class RecordField r l t | r l - t where getField :: l - r - t putField :: l - t - r - r I have once written a short note about how Haskell'98 records could be made more useful using a

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-20 Thread Keean Schupke
Yes, I have unreleased (yet) TH code for generating globally unique labels, and lifting records you can do: $(ttypelift [| data Record = Record { field1 :: Int, field2 :: String } |] ) and it lifts this to an HList style record with labels field1 field2 Labels are assigned unique type

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-20 Thread Keean Schupke
TH has supported multi-parameter classes for a while... new in 6.4 is support for fundeps. Keean. Benjamin Franksen wrote: Two clarifications: On Saturday 19 February 2005 22:33, Benjamin Franksen wrote: instance RecordField R Label_field1 T1 where getField (Rec x _) _ = x putField

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-19 Thread Benjamin Franksen
I think that the best solution is to define record labels as types, or rather type proxies, like for instance in the HList library. This fixes the most important deficiencies of Haskell98 records: - labels are now first class values - labels no longer need to be globally unique, but only unique

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-19 Thread Benjamin Franksen
Two clarifications: On Saturday 19 February 2005 22:33, Benjamin Franksen wrote: instance RecordField R Label_field1 T1 where getField (Rec x _) _ = x putField (Rec _ y) _ v = Rec v x s/Rec/R/ I wonder if something similar could be done with TH. The labels would need

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-18 Thread Keean Schupke
Its a pity template haskell cannot define infix operators, but you could use TH like: $update rec field fn which would expand to: rec { field = fn (rec field) } Keean. S. Alexander Jacobson wrote: I don't know what it takes to get this sort of change into circulation, but I assume it

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-18 Thread S. Alexander Jacobson
On Fri, 18 Feb 2005, Keean Schupke wrote: Its a pity template haskell cannot define infix operators, but you could use TH like: $update rec field fn which would expand to: rec { field = fn (rec field) } That doesn't help you so much if you want to update more than one field at a time. I

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-18 Thread Keean Schupke
Yes, your idea is much nicer... I was just suggesting TH as a way to implement custom syntax... It would be nice if come sort of standard existed for template-haskell so that other compilers/interpreters could adopt it. A portable template would be a cool thing. Keean. S. Alexander

[Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-17 Thread S. Alexander Jacobson
I don't know what it takes to get this sort of change into circulation, but I assume it starts with a clear and specific description of the problem, exploration of alternatives, and a specific proposed solution. So here goes: -- Proposal: Allow \= for field update in record update

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-17 Thread Hal Daume III
There was a long discussion of these issues a while back under the title 'updating labelled fields'. The most recent message was from SPJ: http://www.haskell.org//pipermail/glasgow-haskell-users/2002-May/003374.html You should probably take a look at the whole thread... On Thu, 17 Feb