[Haskell-cafe] Records in Haskell: Type-Indexed Records (another proposal)

2012-03-03 Thread Matthew Farkas-Dyck
Hello all.

I wrote a new proposal for the Haskell record system. It can be found
at http://hackage.haskell.org/trac/ghc/wiki/Records/TypeIndexedRecords

Records are indexed by arbitrary Haskell types. Scope is controlled as
scope of key types. No fieldLabel declarations needed (as in DORF).

Cheers,
strake

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records in Haskell

2012-03-01 Thread AntC
Evan Laforge qdunkan at gmail.com writes:

 [ ccing the list because the wiki page was flawed and I made a bunch
 of changes, hope you don't mind ]
 

Thanks Evan, I've had a quick read through.

It's a bit difficult to compare to the other proposals.

I can't see discussion of extracting higher-ranked functions and applying them 
in polymorphic contexts. (This is SPJ's `rev` example.)

Putting h-r fields into records is the standard way of emulating object-
oriented style. SPJ's view is that requirement is very important in practice.

(No proposal has a good answer to updating h-r's, which you do discuss.)


Re the cons 1. Still can't have two records with the same field name in the 
same module since it relies on modules for namespacing.

Did you see the DORF precursor page ? 
http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
/NoMonoRecordFields

I tried to figure out if that would help, but I suspect not. (Looking at the 
desugar for `deriving (Lens)`, you need the H98 field selector functions.) 
Then for me, cons 1. is a show-stopper. (I know you think the opposite.)


I also don't see whether you can 'hide' or make abstract the representation of 
a record type, but still allow read-access to (some of) its fields. Suppose a 
malicious client declares a record with field #a. Can you stop them reading 
and/or updating your field #a whilst still letting them see field #b of your 
record type?


With SDNR, is it possibly to define a polymorphic field selector function? I 
suspect no looking at the desugar for `deriving (Lens)`, but perhaps I've mis-
understood. I mean:
get_a r = ?? #a r -- gets the #a field from any record r

This mechanism then supports the idea of 'virtual' fields -- SPJ's example of 
fullName, built from polymorphic firstName and lastName.


[By the way, did you mean to post to the cafe only? Most of the discussion is 
going on on ghc-users.]


AntC


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records in Haskell

2012-03-01 Thread Evan Laforge
 Thanks Evan, I've had a quick read through.

Thanks for reading and commenting!

 It's a bit difficult to compare to the other proposals.

 I can't see discussion of extracting higher-ranked functions and applying them
 in polymorphic contexts. (This is SPJ's `rev` example.)

 Putting h-r fields into records is the standard way of emulating object-
 oriented style. SPJ's view is that requirement is very important in 
 practice.

 (No proposal has a good answer to updating h-r's, which you do discuss.)

Yeah, I've never wanted that kind of thing.  I've written in
object-oriented languages so it's not just that I'm not used to the
feature so I don't feel its lack.  And if I did want it, I would
probably not mind falling back to the traditional record syntax,
though I can see how people might find that unsatisfying.  But my
suggestion is meant to solve only the problem of composed record
updates and redundant things in 'Thing.thing_field thing'.  Not
supporting higher-ranked function record fields *only* means that you
can't use this particular convenience to compose updates to a
higher-ranked field.  If you happen to have that particular
intersection of requirements then you'll have to fall back to typing
more things for that particular update.

My motivation is to solve an awkward thing about writing in haskell as
it is, not add a new programming style.

 Re the cons 1. Still can't have two records with the same field name in the
 same module since it relies on modules for namespacing.

 Did you see the DORF precursor page ?
 http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFields
 /NoMonoRecordFields

 I tried to figure out if that would help, but I suspect not. (Looking at the
 desugar for `deriving (Lens)`, you need the H98 field selector functions.)
 Then for me, cons 1. is a show-stopper. (I know you think the opposite.)

Yeah, I don't think the DORF precursor stuff is related, because it's
all based on typeclasses.  I think there are two places where people
get annoyed about name clashes.  One is where they really want to have
two records with the same field name defined in one module.  The other
is where they are using unqualified imports to shorten names and get a
clash from records in different modules.  Only the former is a
problem, the latter should work just fine with my proposal because ghc
lets you import clashing names as long as you don't call them
unqualified, and SDNR qualifies them for you.

So about the former... I've never had this problem, though the point
about circular imports forcing lots of things into the same module is
well taken, I have experienced that.  In that case: nested modules.
It's an orthogonal feature that can be implemented and enabled
separately, and can be useful in other ways too, and can be
implemented separately.  If we are to retain modules as *the* way to
organize namespaces and visibility then we should think about
fancying-up modules when a namespacing problem comes up.

Otherwise you're talking about putting more than one function into one
symbol, and that's typeclasses, and now you have to think of something
clever to counteract typeclasses' desire to be global (e.g. type
proxies).  Maybe that's forcing typeclasses too far beyond their
power/weight compromise design?

 I also don't see whether you can 'hide' or make abstract the representation of
 a record type, but still allow read-access to (some of) its fields.

If you want a read-only field, then don't export the lens for 'a',
export a normal function for it.  However, it would mean you'd use it
as a normal function, and couldn't pass it to 'get' because it's not a
lens, and couldn't be composed together with lenses.  I'd think it
would be possible to put 'get' and 'set' into different typeclasses
and give ReadLenses only the ReadLens dictionary.  But effectively
we'd need subtyping, so a Lens could be casted automatically to a
ReadLens.  I'm sure it's possible to encode with clever rank2 and
existentials and whatnot, but at that point I'm inclined to say it's
too complicated and not worth it.  Use plain functions.  Since 'get'
turns a lens into a plain function, you can still compose with
'#roField . get (#rwField1 . #rwField2)'.

We could easily support 'get (#roField1 . #roField2)' by doing the
ReadLens thing and putting (-) into ReadLens, it's just combining rw
fields and ro fields into the same composition that would require type
gymnastics.

 Suppose a
 malicious client declares a record with field #a. Can you stop them reading
 and/or updating your field #a whilst still letting them see field #b of your
 record type?

I don't think it's worth designing to support malicious clients, but
if you don't want to allow access to a function or lens or any value,
then don't export it.  #a can't resolve to M.a if M doesn't export
'a'.

 With SDNR, is it possibly to define a polymorphic field selector function? I
 suspect no looking at the desugar for `deriving (Lens)`, but perhaps 

Re: [Haskell-cafe] Records in Haskell

2012-02-27 Thread Evan Laforge
[ ccing the list because the wiki page was flawed and I made a bunch
of changes, hope you don't mind ]

 Thanks Evan, but I think that wiki page isn't doing your
 proposal justice. There seem to be several typos in critical
 places that make it hard to follow (for me at least).

Sorry about the sloppy editing.  I updated it and added more detailed
examples.  I also realized that as stated it didn't quite work for
lens updates, so I extended it a little.

 I think it would really help to include a record decl. to
 show where `a` comes from, especially since you say that
 record syntax doesn't change.

Good point, added.

 Could you explain what the TH does. Perhaps give an example
 of what gets generated from a record decl?

Sure, I added an example of that too.

 And perhaps you could explain what you mean by a type
 directed function? Aren't all overloaded functions type
 directed? Can I have both a `#f` and a `f` in scope? What's
 the difference?

The idea is they're not overloaded functions.  #f is not a symbol that
can be in scope, it's special syntax to go *find* a `f` in some
module.  So `x = #f` is not in conflict with `x = f` provided #f is
desugared to SomeModule.f.  Unless of course the argument is defined
in the current module, in which case it will desugar to plain `f` and
then they will be the same.  Since it's syntax for resolving a name,
assigning it like `#f = xyz` doesn't make sense since you can't put a
qualified name on the left of an `=` sign.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records and associated types

2008-12-21 Thread Wolfgang Jeltsch
Am Donnerstag, 11. Dezember 2008 22:04 schrieb Taru Karttunen:
 Hello

 What is the correct way to transform code that uses record selection
 with TypeEq (like HList) to associated types?

Hello Taru,

you might want to look at

http://www.mail-archive.com/glasgow-haskell-users%40haskell.org/msg12788.html

and its follow-ups.

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Records and associated types

2008-12-11 Thread Taru Karttunen
Hello

What is the correct way to transform code that uses record selection
with TypeEq (like HList) to associated types? I keep running into
problems with overlapping type families which is not allowed unless
they match.

The fundep code:

class Select rec label val | rec label - val
instance TypeEq label label True = Select (Label label val :+: rest) label val
instance (Select tail field val) = Select (any :+: tail) field val

And a conversion attempt:

class SelectT rec label where
type S rec label
instance TypeEq label label True = SelectT (Label label val :+: rest) label 
where
type S (Label label val :+: rest) label = val
instance (SelectT tail field) = SelectT (any :+: tail) field where
type S (any :+: tail) field = S tail field

which fails with:

Conflicting family instance declarations:
  type instance S (Label label val :+: rest) label
-- Defined at t.hs:19:9
  type instance S (any :+: tail) field -- Defined at t.hs:23:9


How is it possible to get the TypeEq constraint into the type family?


Attached is a complete example that illustrates the problem.


- Taru Karttunen
{-# LANGUAGE 
  UndecidableInstances, OverlappingInstances, FunctionalDependencies, 
  TypeFamilies, TypeOperators, EmptyDataDecls, GADTs, MultiParamTypeClasses,
  FlexibleInstances
  #-}

-- Fundeps - this works

class Select rec label val | rec label - val
instance TypeEq label label True = Select (Label label val :+: rest) label val
instance (Select tail field val) = Select (any :+: tail) field val


-- Associated types

class SelectT rec label where
type S rec label
instance TypeEq label label True = SelectT (Label label val :+: rest) label where
type S (Label label val :+: rest) label = val

-- THIS FAILS (comment to get this to compile):
instance (SelectT tail field) = SelectT (any :+: tail) field where
type S (any :+: tail) field = S tail field

{-
ERROR:
Conflicting family instance declarations:
  type instance S (Label label val :+: rest) label
-- Defined at t.hs:19:9
  type instance S (any :+: tail) field -- Defined at t.hs:23:9
-}


-- Support code, to get it compile

data True
data False

type family TypeEqR a b
type instance TypeEqR a a = True

class TypeEq a b result
instance (TypeEqR a b ~ isEq, Proxy2 isEq result) = TypeEq a b result

class Proxy2 inp out
instance (result ~ True) = Proxy2 True result
instance (result ~ False) = Proxy2 notTrue result

data End
data (:+:) a b

infixr :+:

newtype Rec wrap rtype = Rec (OuterWrap wrap (R wrap rtype))

type family InnerWrap wrap t :: *
type family OuterWrap wrap t :: *

data R wrap rtype where
End   :: R wrap End
(:+:) :: InnerWrap wrap x - R wrap xs - R wrap (x :+: xs)

data Label l t
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records and associated types

2008-12-11 Thread Ryan Ingram
I don't think you can get a type equality comparison test into type
families without additional compiler support.  If you are willing to
restrict your labels to type-level naturals or some other closed
universe, and allow undecidable instances, you can do something like
this:

data Z   = Z
data S a = S a

type family Select label record
type instance Select lbl (rlbl, ty, rest) = IfEq lbl rlbl ty (Select lbl rest)

type family IfEq n0 n1 t f
type instance IfEq Z Z t f = t
type instance IfEq Z (S n) t f = f
type instance IfEq (S n) Z t f = f
type instance IfEq (S n0) (S n1) t f = IfEq n0 n1 t f

Better support for closed type families that allowed overlap would be
quite useful.

   -- ryan

2008/12/11 Taru Karttunen tar...@taruti.net:
 Hello

 What is the correct way to transform code that uses record selection
 with TypeEq (like HList) to associated types? I keep running into
 problems with overlapping type families which is not allowed unless
 they match.

 The fundep code:

 class Select rec label val | rec label - val
 instance TypeEq label label True = Select (Label label val :+: rest) label 
 val
 instance (Select tail field val) = Select (any :+: tail) field val

 And a conversion attempt:

 class SelectT rec label where
type S rec label
 instance TypeEq label label True = SelectT (Label label val :+: rest) label 
 where
type S (Label label val :+: rest) label = val
 instance (SelectT tail field) = SelectT (any :+: tail) field where
type S (any :+: tail) field = S tail field

 which fails with:

Conflicting family instance declarations:
  type instance S (Label label val :+: rest) label
-- Defined at t.hs:19:9
  type instance S (any :+: tail) field -- Defined at t.hs:23:9


 How is it possible to get the TypeEq constraint into the type family?


 Attached is a complete example that illustrates the problem.


 - Taru Karttunen

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Records: Examples

2007-09-17 Thread Barney Hilken

{-# LANGUAGE TypeFamilies #-}

Hi Justin, thanks for your interest. Hope this helps!

module Examples where
import Records

To get started, you need to define your labels. They are just  
singleton datatypes:


data FirstName = FirstName deriving (Show, Eq, Ord)
data Surname = Surname deriving (Show, Eq, Ord)
data Address = Address deriving (Show, Eq, Ord)
data PhoneNo = PhoneNo deriving (Show, Eq, Ord)

you can define as many as you like. Next you have to define the order  
on fields. At
the moment you have to do this by hand, but I hope to get ghc to do  
this automatically:


type instance NameCmp FirstName FirstName = NameEQ
type instance NameCmp FirstName Surname = NameLT
type instance NameCmp FirstName Address = NameLT
type instance NameCmp FirstName PhoneNo = NameLT
type instance NameCmp Surname FirstName = NameGT
type instance NameCmp Surname Surname = NameEQ
type instance NameCmp Surname Address = NameLT
type instance NameCmp Surname PhoneNo = NameLT
type instance NameCmp Address FirstName = NameGT
type instance NameCmp Address Surname = NameGT
type instance NameCmp Address Address = NameEQ
type instance NameCmp Address PhoneNo = NameLT
type instance NameCmp PhoneNo FirstName = NameGT
type instance NameCmp PhoneNo Surname = NameGT
type instance NameCmp PhoneNo Address = NameGT
type instance NameCmp PhoneNo PhoneNo = NameEQ

Now we are ready to play!

To define records, use (=:) and (+:)

barney = FirstName =: Barney +: Surname =: Hilken +:
Address =: Horwich +: PhoneNo =: 697223

You can use as many or as few of the fields as you like, and you can  
write them in any order,
but trying to use a field twice in the same record will give you a  
(rather incomprehensible)

type error.

	justin = Surname =: Bailey +: FirstName =: Justin +: Address  
=: Somewhere


To extract the value at a field use (.:)

myPhone = barney.:PhoneNo

To delete part of a record, use (-:)

noCallers = barney -: Address

To update existing fields in a record, use (|:)

barney' = barney |: Address =: ((barney .: Address) ++ , UK)

The power of the records system is that these five operators, =:  
+: .: -: |: are Haskell

polymorphic functions. So you can define functions like

livesWith p q = p |: Address =: (q .: Address)

which returns p, but with its Address field changed to that of q.  
Note that this function
works on any records p and q with Address fields, whatever other  
fields they may have.


You can even define functions parametrised by field names:

labelZip n m = zipWith (\x y - n =: x +: m =: y)

then 'labelZip FirstName Surname' is a function which takes two lists  
and returns a list of records:


	names = labelZip FirstName Surname [Barney, Justin] [Hilken,  
Bailey]


of course, labelZip isn't restricted to the four labels we defined  
earlier, it works on anything.



The system is strongly typed, so record errors (such as missing or  
duplicated fields) are caught
at compile time. There are type operators (:=:), (:+:), (:-:), (:.:)  
corresponding to the record
operators, and classes `Contains`, `Disjoint`, `Subrecord` which  
allow you to express conditions
on types. Unfortunately, the type system sometimes decides that a  
function has a different type
from the one you expect, and won't accept the header you want to give  
it. More experience with the

system is needed before we can say whether this is a problem.


Barney.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Antti-Juhani Kaijanaho
Tomasz Zielonka wrote:
 Aren't C and C++ space insensitive (except the preprocessor)?

Literally, yes, because the C and C++ compilers proper take preprocessor
tokens, not strings, as input, and hence do not see the whitespace at
all; the whitespace-sensitive tokenization having been completed by the
preprocessor.  But I think that's splitting hairs, so my answer is: not
in the sense I was using that word. I don't know in what sense you use it.

(In a totally space insensitive language, andy and and y would be
tokenized the same way.)

Personally, I don't see how A.x vs. A . x is much different from that.
When using . as an operator, I separate it by spaces from the other
stuff. (Personally, I would even expect A.x, where A is not a module
name, to be an error in 98-esque Haskell, but it isn't.)
-- 
Antti-Juhani
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 10:39:22AM +0200, Antti-Juhani Kaijanaho wrote:
 Tomasz Zielonka wrote:
  Aren't C and C++ space insensitive (except the preprocessor)?
 (In a totally space insensitive language, andy and and y would be
 tokenized the same way.)

Ah, I was wrong, here are some examples:

int a;  inta;
+ + a;  ++a;
map int, listT  mapint,listT

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-22 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 20:51 schrieb Henning Thielemann:
 On Mon, 21 Nov 2005, Wolfgang Jeltsch wrote:
 [...]

  Hmm, printing code on paper isn't good for the environment.

 But is quite the same argument for e-paper. :-)

I already thought about this.  But if your computer is turned on anyway (as 
usually is mine during my work time), it doesn't make any difference.

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Wolfgang Jeltsch
Am Dienstag, 22. November 2005 07:33 schrieb David Menendez:
 Keean Schupke writes:
  Haskell already has static records (in H98)
 
  Dynamic records are addressed by the HList library, which uses
  extensions already present in GHC and Hugs (namely Multi-parameter
  type-classes and function-dependancies).

 Is this the case? Every implementation of HList that I've seen also uses
 overlapping and undecidable instances.

The paper about HList I have seen does explicitely say that the authors were 
finally able to avoid using overlapping instances.  I don't know about 
undecidable instances but I thought (and hope very much) that they don't need 
them too.

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 20:34 schrieb Max Eronin:
 On 11/21/05, David Roundy [EMAIL PROTECTED] wrote:
  class Coord a where
get_x :: a - Double
get_y :: a - Double
set_x :: Double - a - a
set_y :: Double - a - a

 I'd say this is a typical OO solution to the problem that doesn't exist

 Why do you need setters and getters for coordinate in purely
 functional language? Doesn't  data Coord = Coord Double Double,
 functional composition and monads solve problems in way better than
 inheritance?

 The most impressive feature of haskell for me, as a former OO-design
 patterns-UML is great programmer was that I don't have to and in fact
 must not use OO and inheritance and can write code that doesn't leave
 you guessing what exactly it is doing and what is not. And that the
 language forces you make good design decisions and doesn't let you
 make wrong ones. Inheritance  is no doubt one of the most sensless
 solutions for code reuse i have ever seen.

Yes, yes, yes! :-)

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Keean Schupke
The HList code does not need overlapping-instances, however it does use 
undecidable
instances. This is not however bad like overlapping instances is. 
Overlapping instances
can break module independance (as in defining a new instance can change 
the meaning
of an existing class in modules that are already compiled). Undecidable 
instances merely
means the compiler is not capable of proving that the constraints 
terminate. In the
case of an HList they obviously do (where the constraint recursion is 
structurally over
the length of a list termination is obvious). This is more a weakness in 
the compiler rather

than some problem with the HList code.

   Keean.

Wolfgang Jeltsch wrote:


Am Dienstag, 22. November 2005 07:33 schrieb David Menendez:
 


Keean Schupke writes:
   


   Haskell already has static records (in H98)

   Dynamic records are addressed by the HList library, which uses
extensions already present in GHC and Hugs (namely Multi-parameter
type-classes and function-dependancies).
 


Is this the case? Every implementation of HList that I've seen also uses
overlapping and undecidable instances.
   



The paper about HList I have seen does explicitely say that the authors were 
finally able to avoid using overlapping instances.  I don't know about 
undecidable instances but I thought (and hope very much) that they don't need 
them too.


Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Keean Schupke

My mistake, what you want is:

   (   mything .=. something
   .*. value .=. (27::Int)
   .*. logic .=. True
   .*. HNil )

Admittedly the label creation would benefit from some syntactic sugar to
reduce typing...

Keean.

Bulat Ziganshin wrote:


Hello Keean,

Monday, November 21, 2005, 6:56:06 PM, you wrote:

KS So you can do this now... with reasonable syntax, for example to
KS create an extensible record

KS (some thing .*. (27 :: Int) .*. True .*. HNil)

KS is a statically typed anonymous record.
  
it is not record, but heterogenous list, in my feel. record must be

indexed by field name, not by type name or position


 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Ketil Malde
Cale Gibbard [EMAIL PROTECTED] writes:

 This really isn't so bad in practice though. I've certainly never been
 confused by it. 

Well, what can I say?  Good for you?

 You'd have to go out of your way to construct a
 situation in which it's potentially confusing

No.

 There are much more important issues to deal with than this, really.

Like inventing as many new and wonderful symbolic operators as
possible!  Hey, why not allow quoted function names?  So that I can
defined a function f  different from f  ?  Or differentiate
(+4) from completely different  (+ 4), ( +4) and ( + 4) which
*obviously* are entirely differen things?

 might be relevant in the IOHCC, but not in ordinary programming.

So why not go for the Obfuscated Language Design Contest instead?

 In a sane language, small amounts of whitespace sensitivity are going
 to be around no matter what you do.

And if you already are using whitespace to separate words, surely the
logical (not to mention aesthetical) way forward would be to introduce
evene more whitespace sensitivity - here is the Holy Grail
  http://compsoc.dur.ac.uk/whitespace/index.php 

I don't understand why this isn't obvious to people who generally
appear fairly bright, but: introducing extension that turns working
programs into non-working ones is generally a bad idea.  Having it be
due to spacing habits around symbolic operators is worse.  That
spacing changes suddenly starts bringing very complex language
extensions into the picture, with an associated heap of
incomprehensible error messages is *not* a nice thing for anybody -
except, perhaps, the two academics who wrote the paper, and the three
academics who read it.



/rant

Okay, I'm being unfair here.  Haskell is an academic language, its
primary purpose is to produce papers, not software.  And as a mere
programmer, I'm in a minority.  I think Haskell is really cool, but I
don't really belong here, and I realize of course that my voice isn't
going to carry a lot of weight.

But IF there is a desire for Haskell to be used for Real Work, I think
there should be a certain degree of stability.  Taking the function
composition operator and turning it into record selection -- depending
on spacing, of course -- is, IMO, madness.

But good luck on those papers, and see you later, probably on the
Clean mailing lists. 

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-22 Thread Keean Schupke

Just a follow up to my last post ... The HList paper also presents a way of
removing overlapping instances from _any_ class. So infact support for 
overlapping
instances is no longer required - and this removes all the messy 
problems with

overlapping instances and functional dependancies.

The current HList source distribution runs in hugs with -98 +o only 
because of
lazyness on out part. All the occurances of overlapping instances can 
(will?) be

removed from the source if it becomes an important issue (most of them are
in auxilliary definitions that are not in the paper, like Show for HList.

If you program in the completely non overlapping instances model, then 
compiler

support for deriving TTypeable would be nice, or compiler support for a type
level equality constraint (TypeEq could become a built-in). But just to 
make it clear - compiler
support for this is not necessary, you just define instances of 
TTypeable for all your datatypes.
There is a template-haskell library that can automatically derive 
TTypeable for any datatype

as well.

   Keean.

David Menendez wrote:


Keean Schupke writes:

 


   Haskell already has static records (in H98)

   Dynamic records are addressed by the HList library, which uses 
extensions already present in GHC and Hugs (namely Multi-parameter 
type-classes and function-dependancies).
   



Is this the case? Every implementation of HList that I've seen also uses
overlapping and undecidable instances.
 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Keean Schupke
Just my 2p worth... If I were designing a language I would not have used 
the '.' like Haskell does. One problem is that ascii does not support 
enough symbols (Hmm, PL1 here we come). I guess my vote would go to 
keeping the '.' as is to not break existing programs, and using a 
different symbol for record access and qualified names... however '.' 
works well for DNS names:


   [EMAIL PROTECTED] -- function composition (people are used to reading the @ 
backwards due to emails)

   M.f -- qualified naming...
   f?f -- record access...

really needs more symbols... of course the problem then becomes entering 
them on a normal keyboard.


   Keean.

Ketil Malde wrote:


Cale Gibbard [EMAIL PROTECTED] writes:

 


This really isn't so bad in practice though. I've certainly never been
confused by it. 
   



Well, what can I say?  Good for you?

 


You'd have to go out of your way to construct a
situation in which it's potentially confusing
   



No.

 


There are much more important issues to deal with than this, really.
   



Like inventing as many new and wonderful symbolic operators as
possible!  Hey, why not allow quoted function names?  So that I can
defined a function f  different from f  ?  Or differentiate
(+4) from completely different  (+ 4), ( +4) and ( + 4) which
*obviously* are entirely differen things?

 


might be relevant in the IOHCC, but not in ordinary programming.
   



So why not go for the Obfuscated Language Design Contest instead?

 


In a sane language, small amounts of whitespace sensitivity are going
to be around no matter what you do.
   



And if you already are using whitespace to separate words, surely the
logical (not to mention aesthetical) way forward would be to introduce
evene more whitespace sensitivity - here is the Holy Grail
 http://compsoc.dur.ac.uk/whitespace/index.php 


I don't understand why this isn't obvious to people who generally
appear fairly bright, but: introducing extension that turns working
programs into non-working ones is generally a bad idea.  Having it be
due to spacing habits around symbolic operators is worse.  That
spacing changes suddenly starts bringing very complex language
extensions into the picture, with an associated heap of
incomprehensible error messages is *not* a nice thing for anybody -
except, perhaps, the two academics who wrote the paper, and the three
academics who read it.



/rant

Okay, I'm being unfair here.  Haskell is an academic language, its
primary purpose is to produce papers, not software.  And as a mere
programmer, I'm in a minority.  I think Haskell is really cool, but I
don't really belong here, and I realize of course that my voice isn't
going to carry a lot of weight.

But IF there is a desire for Haskell to be used for Real Work, I think
there should be a certain degree of stability.  Taking the function
composition operator and turning it into record selection -- depending
on spacing, of course -- is, IMO, madness.

But good luck on those papers, and see you later, probably on the
Clean mailing lists. 


-k
 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Sven Panne
I think this discussion has reached a point where it is of utmost importance 
to re-read Wadler's Law of Language Design, a law so fundamental to 
computer science that it can only be compared to quantum dynamics in physics:

   http://www.informatik.uni-kiel.de/~mh/curry/listarchive/0017.html

:-)

Cheers,
   S.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Greg Woodhouse


--- Sven Panne [EMAIL PROTECTED] wrote:

 I think this discussion has reached a point where it is of utmost
 importance 
 to re-read Wadler's Law of Language Design, a law so fundamental to
 
 computer science that it can only be compared to quantum dynamics in
 physics:
 
http://www.informatik.uni-kiel.de/~mh/curry/listarchive/0017.html
 
 :-)
 
 Cheers,
S.

To be honest, I haven't followed the entire records thread (at least
not yet), but I don't know that it's fair to say that we've been
focusing entirely (or nearly so) on lexical issues. I'll grant you that
there's an awful lot of that going on, but unless I'm missin something
obvious, support for a record data type isn't even a purely syntactic
issue. If records are to be supported, they need to have semantics, and
it's not obvious to me how this is to be done in a functional language.

That being said, this is a matter of some interest to me, primarily
because I've been thinking about how to go about using Haskell with
(not necessarily relational) databases, and it seems awkward to use a
tuple or heterogenous list in a context where new attributes can be
added to existing data. Now, of course, that's a puzzle in it's own
right: How on earth can you achieve anything like referential
transparency here? 


===
Gregory Woodhouse  [EMAIL PROTECTED]


Interaction is the mind-body problem of computing.

--Philip Wadler











___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-22 Thread Sven Panne
Am Dienstag, 22. November 2005 19:30 schrieb Greg Woodhouse:
 To be honest, I haven't followed the entire records thread (at least
 not yet), but I don't know that it's fair to say that we've been
 focusing entirely (or nearly so) on lexical issues. I'll grant you that
 there's an awful lot of that going on, but unless I'm missin something
 obvious, support for a record data type isn't even a purely syntactic
 issue. [...]

I definitely didn't want to offend anybody, and I'm sure that there have been 
quite a few good (non-syntactical) proposals, but to be honest: They vanished 
in a sea of syntactic discussions, at least for me, and I couldn't follow the 
whole thread closely due to a lack of time. Hopefully somebody writes up the 
relevant points and proposals in a condensed form...

As an aside, such heated syntactical discussions come up at least once a year 
on the Haskell lists for almost a decade now, and I think it is a good time 
to remind people about the law then... :-)

Cheers,
   S.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Records vs HList

2005-11-22 Thread David Menendez
Keean Schupke writes:

 David Menendez wrote:
 
 Chris Kuklewicz writes:
 
 Would the record system describe at
 http://lambda-the-ultimate.org/node/view/1119
 also be convertable into System Fw, GHC's existing, strongly-typeed
 intermediate language. ?
 
 Probably. Daan's current implementation uses MLF, which I believe is
 system F implemented for ML.
 
 (We're talking about the system in Daan Leijen's paper, Extensible
 Records With Scoped Labels. Good stuff.)

 You can change the project and update operators in the HList library
 to behave in exactly this way. At the moment they are constrained to
 not allow multiple identical labels in records. If this kind of
 access is considered useful, I can add it to the HList distribution.

This is true. I've implemented a small subset of HList that's able to
emulate Daan's three record operators using only fundeps and undecidable
instances.

*Main let r = foo .=. Bar .*. emptyRecord
*Main r
Record{foo=Bar}
*Main let r2 = foo .=. () .*. r  
*Main r2
Record{foo=(),foo=Bar}
*Main r2 .!. foo
()
*Main (r2 .-. foo) .!. foo
Bar

(This is actually *more* powerful than the system described in Daan's
paper, because labels are first class.)

While this is a testament to the power of Haskell's extended type-class
system, I'm not sure that it can replace a dedicated record system. In
his paper, Daan describes how to implement the records such that field
lookups take O(log n) or even O(1) time. HList can't do better than
O(n).

Of course, in the absence of a powerful record system, HList is the way
to go. Rather than decide on a new record system sight unseen, let's
implement them using HList and see how they feel.
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-21 Thread Ketil Malde
Simon Marlow [EMAIL PROTECTED] writes:

 I'm assuming you don't consider the distinction between '::' and ': :'
 to be a problem - the justification for this is simple and logical: a
 double colon '::' is a reserved symbol, in the same way that 'then' is a
 reserved identifier.

Intuitively a contigous string of symbols should form one identifier,
just like a string of letters does.  So '=' is different from ' ='
or ' =' etc.  I suspect I have to make some kind of exception for
nesting/grouping symbols - parentheses and quotes etc.

   - single-line comments  (--??? is not a comment, but -- ??? is)

...so this doesn't bother me so much.

Perhaps we need to either start adopting symbols outside of 7-bit
ASCII?  The other solution is to learn to use actual *names* instead
of inventing ad-hoc strings of symbols.  Haskell code tends to go
overboard with symbolic operators, but in general, it detracts from
the readability and adds to the learning curve.  We don't have to just
because we can. :-)

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[4]: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Jesper Louis Andersen
On Sat, 2005-11-19 at 15:40 +0300, Bulat Ziganshin wrote:

 my 15 CRT holds entire 100, even 102 chars in line and i don't want
 to lose even one of them! :)  especially when comment to this function
 occupies another 7 lines :)

The best argument I can come up with when advocating lines of 80 chars
for most programming code is subtle, but important:

Code is easier to read for me when it is printed on good old paper.
a2ps(1) is magnificient, but it takes 80 chars only if you want two
pages on a single A4. Quite a number of projects violates the 80 column
principle with the result it is unreadable on print.

The human eye is not good at scanning long lines. You tend to miss the
beginning of the next column and has to scan longer for it when reading
code. It helps quite a bit that code is indented though, so it is not
entirely impossible.

I tend to use rather big fonts and not maximize my emacs. I can cram 80
columns in, but no more.



On the other hand, having long lines improves the chance that the
grep(1) catches what you want when searching for context.

You have some empty space in the end of lines to provide a helpful
comment more often than in an 80 column setup.



All in all, this is bikesheds on greener grass (google for bikeshed and
Poul Henning Kamp).


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 08:31 schrieb Bulat Ziganshin:
 Hello Wolfgang,

 Sunday, November 20, 2005, 6:21:05 PM, you wrote:
  data Coord = { x,y :: Double }
  data Point : Coord = { c :: Color }

  A point is not a special coordinate pair.  Instead it has a coordinate
  paar as one of its properties.  So the above-mentioned problem would be
  better handled this way:
 
  data Coord { x, y :: Double }
  data Point = Point {coord :: Coord, c :: Color }

 because this allows a large number of procedures written to work with
 Coord, to automatically work with Point. iy just a matter of
 usability. currently, my program is full of double-dereferncing, like
 this:

 [...]

You should never use bad design to increase usability, I'd say.

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Wolfgang Jeltsch
Am Sonntag, 20. November 2005 12:28 schrieb Jesper Louis Andersen:
 [...]

 The best argument I can come up with when advocating lines of 80 chars
 for most programming code is subtle, but important:

 Code is easier to read for me when it is printed on good old paper.
 a2ps(1) is magnificient, but it takes 80 chars only if you want two
 pages on a single A4. Quite a number of projects violates the 80 column
 principle with the result it is unreadable on print.

Hmm, printing code on paper isn't good for the environment.

 The human eye is not good at scanning long lines.

This is a good argument.

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Sebastian Sylvan
On 11/21/05, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Sonntag, 20. November 2005 12:28 schrieb Jesper Louis Andersen:
  [...]

  The best argument I can come up with when advocating lines of 80 chars
  for most programming code is subtle, but important:
 
  Code is easier to read for me when it is printed on good old paper.
  a2ps(1) is magnificient, but it takes 80 chars only if you want two
  pages on a single A4. Quite a number of projects violates the 80 column
  principle with the result it is unreadable on print.

 Hmm, printing code on paper isn't good for the environment.

  The human eye is not good at scanning long lines.

 This is a good argument.


Also that terminals etc. usually have 80 chars width. It may be time
to stop worrying about code width, especially in languages like
Haskell where you tend to use horizontal rather than vertical space to
write your algorithms. But still, I always try to stick under 80 chars
if possible to make it readible in terminals (and some email-clients
etc.).


/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] records proposals list

2005-11-21 Thread Bulat Ziganshin
Hello Wolfgang,

Monday, November 21, 2005, 1:30:10 PM, you wrote:

  data Coord { x, y :: Double }
  data Point = Point {coord :: Coord, c :: Color }

 because this allows a large number of procedures written to work with
 Coord, to automatically work with Point. iy just a matter of
 usability. currently, my program is full of double-dereferncing, like
 this:

 [...]

WJ You should never use bad design to increase usability, I'd say.

to be exact now i have the following definitions:

data FileInfo = FileInfo
  { fiFilteredName :: !PackedFilePath
  , fiDiskName :: !PackedFilePath
  , fiStoredName   :: !PackedFilePath
  , fiSize :: !FileSize  
  , fiTime :: !FileTime  
  , fiIsDir:: !Bool  
  }

-- |File to compress: either file on disk or compressed file in existing archive
data FileToCompress = DiskFile {
  cfFileInfo :: FileInfo
  }
| CompressedFile {
  cfFileInfo :: FileInfo
, cfArcBlock :: ArchiveBlock-- Archive datablock 
which contains file data
, cfPos  :: FileSize-- Starting byte of 
file data in datablock
, cfCRC  :: CRC -- File's CRC
  }

i prefer to replace second definition with the
  
-- |File to compress: either file on disk or compressed file in existing archive
data CompressedFile : FileInfo =
  CompressedFile {
  cfArcBlock :: ArchiveBlock-- Archive datablock 
which contains file data
, cfPos  :: FileSize-- Starting byte of 
file data in datablock
, cfCRC  :: CRC -- File's CRC
  }

and then use procedures, written to work with FileInfo, to directly
work with CompressedFile also. now my program is full of constructs
like:

  uiStartProcessing (map cfFileInfo (arcDirectory arcinfo))
  let fileinfo  = cfFileInfo compressed_file

and double-dereferencing about i wrote in previous letter. such change
will allow me to omit all these superfluous code. imho, new design will
be more natural and allow me to think about my algorithms instead of
implementation complications

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Wolfgang Jeltsch
Am Montag, 21. November 2005 14:27 schrieb David Roundy:
 On Sun, Nov 20, 2005 at 04:21:05PM +0100, Wolfgang Jeltsch wrote:
  Am Samstag, 19. November 2005 17:35 schrieb Bulat Ziganshin:
   7. OOP-like fields inheritance:
  
   data Coord = { x,y :: Double }
   data Point : Coord = { c :: Color }
  
   of course this is just another sort of syntax sugar once we start
   using classes to define getter/setter functions
 
  I thought that even many OO people say that inheritance of fields is not
  good practice.  So why should we want to support it?

 Think of it instead as being syntactic sugar for a class declaration:

 class Coord a where
   get_x :: a - Double
   get_y :: a - Double
   set_x :: Double - a - a
   set_y :: Double - a - a

As I pointed out in another e-mail just sent, this kind of special syntax only 
solves a very specific problem so that it's questionable whether this syntax 
should be included into Haskell.  However, if we manage to create a more 
generalized approach, inclusion of it into the language might be quite fine.

In addition, having a line which begins with data declaring a class is 
*very* misleading, in my opinion.

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread David Roundy
On Mon, Nov 21, 2005 at 02:48:48PM +0100, Wolfgang Jeltsch wrote:
 Am Montag, 21. November 2005 14:27 schrieb David Roundy:
  On Sun, Nov 20, 2005 at 04:21:05PM +0100, Wolfgang Jeltsch wrote:
   Am Samstag, 19. November 2005 17:35 schrieb Bulat Ziganshin:
7. OOP-like fields inheritance:
   
data Coord = { x,y :: Double }
data Point : Coord = { c :: Color }
   
of course this is just another sort of syntax sugar once we start
using classes to define getter/setter functions
  
   I thought that even many OO people say that inheritance of fields is not
   good practice.  So why should we want to support it?
 
  Think of it instead as being syntactic sugar for a class declaration:
 
  class Coord a where
get_x :: a - Double
get_y :: a - Double
set_x :: Double - a - a
set_y :: Double - a - a
 
 As I pointed out in another e-mail just sent, this kind of special syntax
 only solves a very specific problem so that it's questionable whether
 this syntax should be included into Haskell.  However, if we manage to
 create a more generalized approach, inclusion of it into the language
 might be quite fine.
 
 In addition, having a line which begins with data declaring a class is
 *very* misleading, in my opinion.

Data lines declare instances all the time via deriving.  If something like
this were implemented--and really this applies to any scheme that creates
functions to access record fields--there would need to be a set of implicit
classes for field access.  To fix the namespace issue with field names, the
only two solutions (as far as I can tell) are

(a) Don't create getter or setter functions for field access.  This is what
the SM proposal does.

(b) Create some sort of class that allows getter and/or setter functions
for field access.

(a) involves the creation of a non-function syntax for something that is
essentially a function--and means you'll need boiler-plate code if you want
to create accessor functions.  (b) means a proliferation of classes, which
is perhaps more problematic, but you gain more from it--you avoid the
requirement of a special syntax for accessing fields of a record.  So if
some variant of (b) is practical, I'd vote for it.  I'm not attached to the
inheritance idea, but it's basically a limited form of (b).
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Philippa Cowderoy
On Mon, 21 Nov 2005, David Roundy wrote:

 (b) Create some sort of class that allows getter and/or setter functions
 for field access.
 
 (a) involves the creation of a non-function syntax for something that is
 essentially a function--and means you'll need boiler-plate code if you want
 to create accessor functions.  (b) means a proliferation of classes, which
 is perhaps more problematic, but you gain more from it

I'm not sure it's all that bad if we can avoid namespace pollution?

-- 
[EMAIL PROTECTED]

Performance anxiety leads to premature optimisation
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Keean Schupke

Hi,

   Haskell already has static records (in H98)

   Dynamic records are addressed by the HList library, which uses 
extensions already present in GHC and Hugs (namely Multi-parameter 
type-classes and function-dependancies).


   So you can do this now... with reasonable syntax, for example to 
create an extensible record


   (some thing .*. (27 :: Int) .*. True .*. HNil)

   is a statically typed anonymous record.
  

   In other words there is no need for any more extensions to GHC or 
Hugs to implement Records (although  having a type-level type-equality 
constaint would simplify the internal implementation of the library)...


   For details see the HList paper: http://homepages.cwi.nl/~ralf/HList/

   Regards,  
   Keean.


Bulat Ziganshin wrote:


Hello Haskell,

 can anyone write at least the list of record proposals for Haskell?
or, even better, comment about pros and contras for each proposal?

 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] records proposals list

2005-11-21 Thread Bulat Ziganshin
Hello Keean,

Monday, November 21, 2005, 6:56:06 PM, you wrote:

KS So you can do this now... with reasonable syntax, for example to
KS create an extensible record

KS (some thing .*. (27 :: Int) .*. True .*. HNil)

KS is a statically typed anonymous record.
   
it is not record, but heterogenous list, in my feel. record must be
indexed by field name, not by type name or position


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] records proposals list

2005-11-21 Thread Ralf Lammel
I certainly agree with Keean. It's just that the given example is a bit
misleading. As Bulat observed, the example is about a heterogeneous
list, as opposed to a record. But there are of course tons of record
examples to be found, if you follow the HList link.

Ralf

P.S.: The HList paper also has a reasonable related work section, which
might hold more information of the kind that Bulat asked for.


 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Keean Schupke
 Sent: Monday, November 21, 2005 7:56 AM
 To: Bulat Ziganshin
 Cc: Haskell Cafe
 Subject: Re: [Haskell-cafe] records proposals list
 
 Hi,
 
 Haskell already has static records (in H98)
 
 Dynamic records are addressed by the HList library, which uses
 extensions already present in GHC and Hugs (namely Multi-parameter
 type-classes and function-dependancies).
 
 So you can do this now... with reasonable syntax, for example to
 create an extensible record
 
 (some thing .*. (27 :: Int) .*. True .*. HNil)
 
 is a statically typed anonymous record.
 
 
 In other words there is no need for any more extensions to GHC or
 Hugs to implement Records (although  having a type-level type-equality
 constaint would simplify the internal implementation of the
library)...
 
 For details see the HList paper:
http://homepages.cwi.nl/~ralf/HList/
 
 Regards,
 Keean.
 
 Bulat Ziganshin wrote:
 
 Hello Haskell,
 
   can anyone write at least the list of record proposals for Haskell?
 or, even better, comment about pros and contras for each proposal?
 
 
 
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Keean Schupke
You can change the project and update operators in the HList library to 
behave
in exactly this way. At the moment they are constrained to not allow 
multiple
identical labels in records. If this kind of access is considered 
useful, I can

add it to the HList distribution.

   Keean.

David Menendez wrote:


Chris Kuklewicz writes:

 


Would the record system describe at
http://lambda-the-ultimate.org/node/view/1119
also be convertable into System Fw, GHC's existing, strongly-typeed
intermediate language. ?
   



Probably. Daan's current implementation uses MLF, which I believe is
system F implemented for ML.

(We're talking about the system in Daan Leijen's paper, Extensible
Records With Scoped Labels. Good stuff.)
 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Keean Schupke
Can this not be done with the HList code? I am pretty sure you should be 
able to
map projections over HLists of HLists... (although the HList generic map 
is a bit

ugly, requiring instances of the Apply class).

Actually you should look in the OOHaskell paper (if you haven't already) 
where it

discusses using narrow to allow homogeneous lists to be projected from
heterogeneous ones...

   Keean.

John Meacham wrote:


another thing is that for any record syntax, we would want higher order
versions of the selection, setting, and updating routines. A quick
perusal of my source code shows over half my uses of record selectors
are in a higher order fashion. (which need to be generated with DrIFT
with the current syntax)

I mean something like 


map (.foo) xs
to pull all the 'foo' fields out of xs.  (using made up syntax)

or 


map (foo_s 3) xs

to set all the foo fields to 3. (using DrIFT syntax)


   John

 



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Malcolm Wallace
David Roundy [EMAIL PROTECTED] writes:

 I'd benefit from just a list of problems that the record proposals want to
 solve.
 
 1. The field namespace issue.
 2. Multi-constructor getters, ideally as a function.
 3. Safe getters for multi-constructor data types.
 4. Getters for multiple data types with a common field.
 5. Setters as functions.
 6. Anonymous records.
 7. Unordered records.

Personally, I would quite like to have first-class labels.  By this
I mean the ability to pass record labels as arguments, and to return
them as results.

With this one generalisation, it would be possible to cover most of
the wishlist above.  A generic getter and setter could be defined
simply as polymorphic functions e.g.

get :: Label n - Record (n::a | r) - a
set :: Label n - a - Record r - Record (n::a | r)
upd :: Label n - (a-a) - Record (n::a | r) - Record (n::a | r)

You could even define your own preferred syntactic sugar for these
operations e.g.

r . l = get l r

.. and the higher-order uses fall out for free

map (get foo) listOfRecords

There are several proposals incorporating this idea.

Oleg Kiselyov and Ralf Lämmel, Haskell's overlooked object system
http://homepages.cwi.nl/~ralf/OOHaskell/

Daan Leijen, First-class labels for extensible rows
http://www.cs.uu.nl/~daan/pubs.html

Benedict Gaster and Mark Jones, A Polymorphic Type System for
Extensible Records and Variants
http://www.cse.ogi.edu/~mpj/pubs/polyrec.html

Regards,
Malcolm
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Max Eronin
On 11/21/05, David Roundy [EMAIL PROTECTED] wrote:
 class Coord a where
   get_x :: a - Double
   get_y :: a - Double
   set_x :: Double - a - a
   set_y :: Double - a - a


I'd say this is a typical OO solution to the problem that doesn't exist

Why do you need setters and getters for coordinate in purely
functional language? Doesn't  data Coord = Coord Double Double,
functional composition and monads solve problems in way better than
inheritance?
The most impressive feature of haskell for me, as a former OO-design
patterns-UML is great programmer was that I don't have to and in fact
must not use OO and inheritance and can write code that doesn't leave
you guessing what exactly it is doing and what is not. And that the
language forces you make good design decisions and doesn't let you
make wrong ones. Inheritance  is no doubt one of the most sensless
solutions for code reuse i have ever seen.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread Henning Thielemann


On Sat, 19 Nov 2005, David Roundy wrote:


1. Field namespace issue:

Field names should not need to be globally unique.  In Haskell 98, they
share the function namespace, and must be unique.  We either need to make
them *not* share the function namespace (which means no getters as
functions), or somehow stick the field labels into classes.


I found that problem more annoying when starting with Haskell. But since I 
do now try to define only one data type per module, equal field names 
don't collide so easy anymore. It remains the inconvenience that field 
names must be qualified with the module name rather than the record 
variable name.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-21 Thread Henning Thielemann


On Sat, 19 Nov 2005, Antti-Juhani Kaijanaho wrote:


Ketil Malde wrote:
[about A.b and A . b potentially meaning different things:]

Syntax that changes depending on spacing is my number
one gripe with the Haskell syntax


I also think that it is problematic that a character which can be part of 
an alpha-numeric identifier can also be part of an infix operator 
identifier. This is the cause of the relevance of the spacing. 'A+b' and 
'A + b' always mean the same, but 'A.b' and 'A . b' do not. Very 
confusing.



Hence, spacing being significant is not Haskell-specific


So Haskell is somehow BASICish -- how awful.


and is generally a good thing.


FORTRAN is even more space sensitive ...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Henning Thielemann


On Mon, 21 Nov 2005, Wolfgang Jeltsch wrote:


Am Sonntag, 20. November 2005 12:28 schrieb Jesper Louis Andersen:

[...]



The best argument I can come up with when advocating lines of 80 chars
for most programming code is subtle, but important:

Code is easier to read for me when it is printed on good old paper.
a2ps(1) is magnificient, but it takes 80 chars only if you want two
pages on a single A4. Quite a number of projects violates the 80 column
principle with the result it is unreadable on print.


Hmm, printing code on paper isn't good for the environment.


But is quite the same argument for e-paper. :-)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-21 Thread Cale Gibbard
On 21/11/05, Henning Thielemann [EMAIL PROTECTED] wrote:

 On Sat, 19 Nov 2005, Antti-Juhani Kaijanaho wrote:

  Ketil Malde wrote:
  [about A.b and A . b potentially meaning different things:]
  Syntax that changes depending on spacing is my number
  one gripe with the Haskell syntax

 I also think that it is problematic that a character which can be part of
 an alpha-numeric identifier can also be part of an infix operator
 identifier. This is the cause of the relevance of the spacing. 'A+b' and
 'A + b' always mean the same, but 'A.b' and 'A . b' do not. Very
 confusing.

This really isn't so bad in practice though. I've certainly never been
confused by it. You'd have to go out of your way to construct a
situation in which it's potentially confusing, which is something that
might be relevant in the IOHCC, but not in ordinary programming.

There are much more important issues to deal with than this, really.

In a sane language, small amounts of whitespace sensitivity are going
to be around no matter what you do. We use whitespace to denote
function application. I can't write fx to mean f x. This is a good
thing. The same perhaps ought to apply to operators. It would be nice
sometimes to be able to use '-' as a hyphen in the middle of names.

 - Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-21 Thread Max Eronin
On 11/18/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:

 I'm not saying it's impossible to make good use of (.), I'm saying
 that it's not crucial enough to warrant giving it the dot, which in my
 opinion is one of the best symbols (and I'd hand it over to record
 selection any day of the week!).
 I'm also saying that people tend to abuse the (.) operator when they
 start out because they think that less verbose == better, whereas
 most people, in my experience, tend to stop using (.) for all but the
 simplest cases (such as filte (not . null)) after a while to promote
 readability. I prefer adding a few lines with named sub-expressions to
 make things clearer.


In case someone counts votes pro et contra of replacing (.) operator,
I must say that find it one of the most useful and readable way for
doing many different things (not only higher-order). And very compact
too.
And in my code it is very common operator.
While if somebody, who at this moment counts my vote, will remove
records from the language some day, I very likely wouldn't notice such
a loss.
And I can't say I'm very experienced haskell programmer. Actually I'm
a beginner comparing my experience with other, particularly imperative
OOP languages.
And records with (.) as field selector (coupled with dumb
constructors) will be the last thing i would miss in haskell.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-21 Thread Antti-Juhani Kaijanaho
Henning Thielemann wrote:
 Hence, spacing being significant is not Haskell-specific
 
 So Haskell is somehow BASICish -- how awful.

No, you got it backwards. I was contrasting a BASIC dialect as an
example of a space-*in*sensitive language to just about every modern
language, including Haskell.  In other words, Haskell was specifically
*not* like BASIC in my comparison.

I believe early FORTRAN is another example of a spacing-*in*sensitive
language comparable to that BASIC dialect, and *not* similar to Haskell.
-- 
Antti-Juhani
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-21 Thread David Menendez
Keean Schupke writes:

 Haskell already has static records (in H98)
 
 Dynamic records are addressed by the HList library, which uses 
 extensions already present in GHC and Hugs (namely Multi-parameter 
 type-classes and function-dependancies).

Is this the case? Every implementation of HList that I've seen also uses
overlapping and undecidable instances.
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-21 Thread Tomasz Zielonka
On Tue, Nov 22, 2005 at 07:09:33AM +0200, Antti-Juhani Kaijanaho wrote:
 Henning Thielemann wrote:
  Hence, spacing being significant is not Haskell-specific
  
  So Haskell is somehow BASICish -- how awful.
 
 No, you got it backwards. I was contrasting a BASIC dialect as an
 example of a space-*in*sensitive language to just about every modern
 language, including Haskell.  In other words, Haskell was specifically
 *not* like BASIC in my comparison.
 
 I believe early FORTRAN is another example of a spacing-*in*sensitive
 language comparable to that BASIC dialect, and *not* similar to Haskell.

Aren't C and C++ space insensitive (except the preprocessor)?

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] records proposals list

2005-11-20 Thread Benjamin Franksen
On Saturday 19 November 2005 17:35, Bulat Ziganshin wrote:
 Hello David,

 Saturday, November 19, 2005, 4:57:09 PM, you wrote:

 DR I'd benefit from just a list of problems that the record
 proposals want to DR solve.

 DR 1. The field namespace issue.
 DR 2. Multi-constructor getters, ideally as a function.
 DR 3. Safe getters for multi-constructor data types.
 DR 4. Getters for multiple data types with a common field.
 DR 5. Setters as functions.
 DR 6. Anonymous records.
 DR 7. Unordered records.

 DR Argh.  When I think about records too long I get dizzy.

 really you are wrote solutions for all these problems (except 6), and
 it's just an additional syntax sugar (like the fields itself). for
 beginning, we must split this list to two parts: belonging to static
 (like H98) and dynamic (anonymous) records. items in your list
 (except 6) belongs to static ones. dynamic records is whole different
 beast and it's really hard to master, so the first question will be:

 are we wanna to have in Haskell only static records, only dynamic
 records or both?

 as i see, GHC team want to implement such proposal, which will
 resolve both issues. and wainting (waiting+wanting:) for such
 solution, they are don't implement suggestions which address only
 static records problems

 but the dynamic records is too complex thing: it may be syntactically
 incompatible with H98, it may require changes to GHC internals and so
 on, so they are delayed until better times


 besides this all, i want to add one more item to your list:

 7. OOP-like fields inheritance:

 data Coord = { x,y :: Double }
 data Point : Coord = { c :: Color }

 of course this is just another sort of syntax sugar once we start
 using classes to define getter/setter functions

Please take a look at the recent paper by Daan Leijen 
(http://www.cs.uu.nl/~daan/pubs.html#scopedlabels). I think this would 
solve the mentioned problems and has the additional advantage of 
supporting anonymous records. The author claims his proposal to be 
integrable with most known type systems.

Ben
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Records

2005-11-20 Thread Simon Marlow
On 19 November 2005 20:53, Ketil Malde wrote:

 Antti-Juhani Kaijanaho wrote:
 
 Ketil Malde wrote:
 [about A.b and A . b potentially meaning different things:]
 
 
 Syntax that changes depending on spacing is my number
 one gripe with the Haskell syntax
 
 
 
 I've generally considered that one of the good ideas in most current
 languages (it's not specific to Haskell). ISTR there was a Basic
  dialect where IFX=0THENX=X+1
 and
  IF X = 0 THEN X = X + 1
 meant the same thing.
 
 
 My point is that e.g. currently foo? bar, foo ?bar and foo ? bar
 have (at least two) different meanings.   Hierarchical naming collides
 with function composition (admittedly only rarely in practice).
 Template haskell collides with list comprehensions.
 
 Do you really think that is such a great idea?

I think many people agree that this is a bad thing.  It occurs in two
places in Haskell 98, I believe:

  - qualified identifiers (M.T is different from M . T)
  
  - single-line comments  (--??? is not a comment, but -- ??? is)

Both of these were late additions to Haskell, and if we were starting
from scratch the syntax would probably not have such anomalies.  The
other odd cases that GHC has are all extensions too - you mentioned
implicit parameters and template haskell, there is also GHC's unboxed
values (1#, (#..#)), arrows, and parrays.  I would argue against adding
any of these syntactic anomalies to the standard language, and we should
strive to remove those that we have (e.g. by deprecating the use of '.'
as function composition in favour of something else, thus freeing it up
for use as record/module selection).

I'm assuming you don't consider the distinction between '::' and ': :'
to be a problem - the justification for this is simple and logical: a
double colon '::' is a reserved symbol, in the same way that 'then' is a
reserved identifier.

Cheers,
Simon
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Records

2005-11-20 Thread Philippa Cowderoy
On Sun, 20 Nov 2005, Simon Marlow wrote:

 I'm assuming you don't consider the distinction between '::' and ': :'
 to be a problem - the justification for this is simple and logical: a
 double colon '::' is a reserved symbol, in the same way that 'then' is a
 reserved identifier.
 

I have to admit that even if it weren't my expectation would be for '::' 
to parse as one operator and complain (of course, as ': :' the odds of it 
being used in a situation where it typechecks are rather low).

-- 
[EMAIL PROTECTED]

The task of the academic is not to scale great 
intellectual mountains, but to flatten them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-20 Thread Wolfgang Jeltsch
Am Samstag, 19. November 2005 17:35 schrieb Bulat Ziganshin:
 [...]

 7. OOP-like fields inheritance:

 data Coord = { x,y :: Double }
 data Point : Coord = { c :: Color }

 of course this is just another sort of syntax sugar once we start
 using classes to define getter/setter functions

I thought that even many OO people say that inheritance of fields is not good 
practice.  So why should we want to support it?

A point is not a special coordinate pair.  Instead it has a coordinate paar as 
one of its properties.  So the above-mentioned problem would be better 
handled this way:

data Coord { x, y :: Double }
data Point = Point {coord :: Coord, c :: Color }

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] records proposals list

2005-11-20 Thread Bulat Ziganshin
Hello Wolfgang,

Sunday, November 20, 2005, 6:21:05 PM, you wrote:

 data Coord = { x,y :: Double }
 data Point : Coord = { c :: Color }

WJ A point is not a special coordinate pair.  Instead it has a coordinate paar 
as 
WJ one of its properties.  So the above-mentioned problem would be better 
WJ handled this way:

WJ data Coord { x, y :: Double }
WJ data Point = Point {coord :: Coord, c :: Color }

because this allows a large number of procedures written to work with
Coord, to automatically work with Point. iy just a matter of
usability. currently, my program is full of double-dereferncing, like
this:

  if (fiTime (cfFileInfo arcfile) = fiTime (cfFileInfo diskfile))
  maximum (last_time' : map (fiTime.cfFileInfo) dir)
  let size =  fiSize  (cfFileInfo cfile')
  bytes = sum$ map (fiSize.cfFileInfo) directory
  let keyFunc  =  fiStoredName . cfFileInfo


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-19 Thread Bulat Ziganshin
Hello John,

Saturday, November 19, 2005, 2:25:47 AM, you wrote:

JM  grep -o ' [-+.*/[EMAIL PROTECTED] ' GenUtil.hs | sort | uniq -c | sort -n
JM  30  .

JM one of the most common operators.

especially in comments ;)  add the following filter to strip them:

import System.Environment

main = interact (noStream.(unlines.map noEnd.lines))

noStream ('{':'-':xs) = noInStream xs
noStream (c:xs)   = c:noStream xs
noStream= 

noInStream ('-':'}':xs) = noStream xs
noInStream (_:xs)   = noInStream xs
noInStream= 

noEnd ('-':'-':xs) = 
noEnd (c:xs)   = c:noEnd xs
noEnd= 


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[4]: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-19 Thread Bulat Ziganshin
Hello Sebastian,

Friday, November 18, 2005, 6:35:13 PM, you wrote:

 groupLen mapper combinator tester  =  length . takeWhile tester . scanl1 
 combinator . map mapper

SS This is a border line example of what I would consider being abuse of
SS the (.) operator.
SS First of all, that line is 96 characters long. A bit much if you ask
SS me.

my 15 CRT holds entire 100, even 102 chars in line and i don't want
to lose even one of them! :)  especially when comment to this function
occupies another 7 lines :)

SS groupLen' mapper combinator tester xs
SS= length $ takeWhile tester $ scanl1 combinator $ map mapper xs

SS The difference is minimal, if anything I think that writing out the
SS list argument is actually clearer in this case (although there are
SS cases when you want to work on functions, and writing out the
SS parameters makes things less clear).

... including this one. i'm work with functions, when possible: build
them from values and other functions, hold them in datastructures,
pass and return them to/from functions. if function definition can be
written w/o part of its arguments, i do it in most cases

moreover, in some cases this leads to dramatic changes in speed. see:

-- |Test whether `filepath` meet one of filemasks `filespecs`
match_filespecs filespecs {-filepath-}  =  any_function (map match_FP filespecs)

function `match_FP` thranslates regexps to functions checking that
given filename match this regular expression:

match_FP :: RegExp - (String-Bool)

when definition of `match_filespecs` contained `filepath`, this
testing works very slow for large filelists. imho, for each filename
list of filespecs was retranslated to testing functions, each
function applied to filename and then results was combined by
`any_function`. it's a pity, especially cosidering that most common
case for regexps list was just [*], which must render to
(const True) testing function. so, in this case it was absolutely
necessary to write all this regexp machinery in point-free style, so that
it returns data-independent functions, which then optimized
(reduced) by Haskell evaluator before applying them to filenames

on the Wiki page RunTimeCompilation there is another examples of
building functions from datastructures before applying to input data

it is very possible that this point-free `groupLen` definition,
together with other point-free definitions, makes filelist processing
in my program faster - i just dont't checked it

SS I'm not saying it's impossible to make good use of (.), I'm saying
SS that it's not crucial enough to warrant giving it the dot, which in my
SS opinion is one of the best symbols (and I'd hand it over to record
SS selection any day of the week!).
SS I'm also saying that people tend to abuse the (.) operator when they
SS start out because they think that less verbose == better, whereas
SS most people, in my experience, tend to stop using (.) for all but the
SS simplest cases (such as filte (not . null)) after a while to promote
SS readability. I prefer adding a few lines with named sub-expressions to
SS make things clearer.

readability is not some constant factor for all people. it depends
on your experience. for you it is natural to work with data values.
for me, it's the same natural to work with function values, partially
apply and combine them. and in those definitions the variables
containing actual data is just looks as garbage for me

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-19 Thread David Roundy
On Fri, Nov 18, 2005 at 05:42:41PM +0300, Bulat Ziganshin wrote:
   can anyone write at least the list of record proposals for Haskell?
 or, even better, comment about pros and contras for each proposal?

I'd benefit from just a list of problems that the record proposals want to
solve.

I can list the issues that seem important to me, but I am sure my list
isn't complete.  Also note that some of these goals may be mutually
contradictory, but agreeing on the problems might help in agreeing on the
solutions.

A getter is a way to get a field out of a record, a setter is a way to
update a field in a record.  These may be either pattern-matching syntaxes,
functions or some other odd syntax.

Here's the quick summary, expanded below:

1. The field namespace issue.
2. Multi-constructor getters, ideally as a function.
3. Safe getters for multi-constructor data types.
4. Getters for multiple data types with a common field.
5. Setters as functions.
6. Anonymous records.
7. Unordered records.

2. Multi-constructor getters.

1. Field namespace issue:

Field names should not need to be globally unique.  In Haskell 98, they
share the function namespace, and must be unique.  We either need to make
them *not* share the function namespace (which means no getters as
functions), or somehow stick the field labels into classes.

2. Multi-constructor getters, ideally as a function:

An accessor ought to be able to access an identically-named field from
multiple constructors of a given data type:

 data FooBar = Foo { name :: String } | Bar { name :: String }

However we access name, we should be able to access it from either
constructor easily (as Haskell 98 does, and we'd like to keep this).

3. Safe getters for multi-constructor data types.

Getters ought to be either safe or explicitly unsafe when only certain
constructors of a data type have a given field (this is my pet peeve):

 data FooBar = Foo { foo :: String } | Bar { bar :: String }

This shouldn't automatically generate a function of type

 foo :: FooBar - String

which will fail when given a FooBar of the Bar constructor.  We can always
write this function ourselves if we so desire.

4. Getters for multiple data types with a common field.

This basically comes down to deriving a class for each named field, or
something equivalent to it, as far as I can tell.  This also works with the
namespace issue, since if we are going to define getters and setters as
functions, we either need unique field labels or we need one class per
field label--or something equivalent to a class for each field label.

5. Setters as functions.

It would be nice to have a setter function such as (but with perhaps a
better name)

 set_foo :: String - Foo - Foo

be automatically derived from

 data Foo = Foo { foo :: String }

in the same way that in Haskell 98 foo :: Foo - String is implicitely
derived.

Note that this opens up issues of safety when you've got multiple
constructors, and questions of how to handle setting of a field that isn't
in a particular datum.

6. Anonymous records.

This idea is from Simon PJ's proposal, which is that we could have
anonymous records which are basically tuples on steroids.  Strikes me as a
good idea, but requires that we address the namespace question, that is,
whether field labels share a namespace with functions.  In Simon's
proposal, they don't.

This is almost a proposal rather than an issue, but I think that it's a
worthwhile idea in its own right.

7. Unordered records.

I would like to have support for unordered records, which couldn't be
matched or constructed by field order, so I could (safely) reorder the
fields in a record.  This is really an orthogonal issue to pretty much
everything else.


Argh.  When I think about records too long I get dizzy.
-- 
David Roundy
http://www.darcs.net
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-19 Thread Wolfgang Jeltsch
Am Samstag, 19. November 2005 14:57 schrieb David Roundy:
 [...]

 2. Multi-constructor getters, ideally as a function:

 An accessor ought to be able to access an identically-named field from

 multiple constructors of a given data type:
  data FooBar = Foo { name :: String } | Bar { name :: String }

 However we access name, we should be able to access it from either
 constructor easily (as Haskell 98 does, and we'd like to keep this).

Let's take a concrete example.  Say, I have a type Address which is declared 
as follows:

data Address = OrdinaryAddr {
name :: String,
street :: String,
number :: Int,
city :: String,
postalCode :: Int
} | POBoxAddr {
name :: String,
poBox :: Int,
city :: String,
postalCode :: Int
}

In this example, it would be really good if there was a getter function for 
extracting the name out of an ordinary address as well as an PO box address.  
But in my opinion, the above declaration is not very nice and one should 
write the following instead:

data Address = Address {
name :: String,
destination :: Destination,
city :: String,
postalCode :: Int
}

data Destination = OrdinaryDest {
street :: String,
number :: Int
} | POBoxDest {
poBox :: Int
}

And with this declaration we wouldn't need getter functions which are able to 
access identically-named fields from different data constructors of the same 
type.  So I wonder if this feature is really sensible.

 [...]

Best wishes,
Wolfgang
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-19 Thread Antti-Juhani Kaijanaho
Ketil Malde wrote:
[about A.b and A . b potentially meaning different things:]
 Syntax that changes depending on spacing is my number
 one gripe with the Haskell syntax

I've generally considered that one of the good ideas in most current
languages (it's not specific to Haskell). ISTR there was a Basic dialect
where
  IFX=0THENX=X+1
and
  IF X = 0 THEN X = X + 1
meant the same thing. If that dialect had allowed multi-character
variable names (which I think it didn't), ANDY would have been parsed as
AND Y instead of the simple variable ANDY.

Hence, spacing being significant is not Haskell-specific and is
generally a good thing.

-- 
Antti-Juhani
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-19 Thread Ketil Malde

Antti-Juhani Kaijanaho wrote:


Ketil Malde wrote:
[about A.b and A . b potentially meaning different things:]
 


Syntax that changes depending on spacing is my number
one gripe with the Haskell syntax
   



I've generally considered that one of the good ideas in most current
languages (it's not specific to Haskell). ISTR there was a Basic dialect
where
 IFX=0THENX=X+1
and
 IF X = 0 THEN X = X + 1
meant the same thing. 
 

My point is that e.g. currently foo? bar, foo ?bar and foo ? bar 
have (at least two) different meanings.   Hierarchical naming collides 
with function composition (admittedly only rarely in practice).  
Template haskell collides with list comprehensions.


Do you really think that is such a great idea?

-k

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] records proposals list

2005-11-19 Thread Bulat Ziganshin
Hello David,

Saturday, November 19, 2005, 4:57:09 PM, you wrote:

DR I'd benefit from just a list of problems that the record proposals want to
DR solve.

DR 1. The field namespace issue.
DR 2. Multi-constructor getters, ideally as a function.
DR 3. Safe getters for multi-constructor data types.
DR 4. Getters for multiple data types with a common field.
DR 5. Setters as functions.
DR 6. Anonymous records.
DR 7. Unordered records.

DR Argh.  When I think about records too long I get dizzy.

really you are wrote solutions for all these problems (except 6), and
it's just an additional syntax sugar (like the fields itself). for
beginning, we must split this list to two parts: belonging to static
(like H98) and dynamic (anonymous) records. items in your list (except
6) belongs to static ones. dynamic records is whole different beast
and it's really hard to master, so the first question will be:

are we wanna to have in Haskell only static records, only dynamic
records or both?

as i see, GHC team want to implement such proposal, which will resolve
both issues. and wainting (waiting+wanting:) for such solution, they
are don't implement suggestions which address only static records
problems

but the dynamic records is too complex thing: it may be syntactically
incompatible with H98, it may require changes to GHC internals and so
on, so they are delayed until better times


besides this all, i want to add one more item to your list:

7. OOP-like fields inheritance:

data Coord = { x,y :: Double }
data Point : Coord = { c :: Color }

of course this is just another sort of syntax sugar once we start
using classes to define getter/setter functions


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] records proposals list

2005-11-19 Thread Dimitry Golubovsky

David Roundy wrote:



4. Getters for multiple data types with a common field.



[skip]



4. Getters for multiple data types with a common field.

This basically comes down to deriving a class for each named field, or
something equivalent to it, as far as I can tell.  This also works with the
namespace issue, since if we are going to define getters and setters as
functions, we either need unique field labels or we need one class per
field label--or something equivalent to a class for each field label.


This is a problem similar to one I had to solve for HSFFIG to design a 
syntax to access fields of C structures (where different structures may 
have fields of same name but of different types).


I ended up with a multiparameter class parameterized by a C structure 
name, field name, field type, and for each occurrence of these in C 
header file I autogenerated an instance of this class.


See

http://hsffig.sourceforge.net/repos/hsffig-1.0/_darcs/current/HSFFIG/FieldAccess.hs

for the class itself, and a typical instance (autogenerated of course) 
looked like


instance HSFFIG.FieldAccess.FieldAccess S_362 ((CUChar)) V_byteOrder where
  z -- V_byteOrder = ((\hsc_ptr - peekByteOff hsc_ptr 0)) z
{-# LINE 5700 XPROTO_H.hsc #-}
  (z, V_byteOrder) -- v = ((\hsc_ptr - pokeByteOff hsc_ptr 0)) z v
{-# LINE 5701 XPROTO_H.hsc #-}

for a field `byteOrder' of type `unsigned char'.

This might work in general for what is proposed in the item 4 quoted 
above. A class with 3 parameters will be needed, and perhaps some 
syntactic sugar to autogenerate it and its instances. The only downside 
is GHC needs too much memory to compile all this: I had to add a 
splitter utility to HSFFIG otherwise GHC failed short of memory on even 
several tens of C structures.


Dimitry Golubovsky
Middletown, CT

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Glynn Clements

Sebastian Sylvan wrote:

   How about (¤)? It looks like a ring to me, I'm not sure where that's
   located on a EN keyboard, but it's not terribly inconvenient on my SE
   keyboard. f ¤ g looks better than f . g for function composition, if
   you ask me.
  
  That symbol actually does look better, but isn't on any English
  keyboards to the best of my knowledge. I can get it in my setup with
  compose-key o x, but not many people have a compose key assigned.
  Also, this may just be a bug, but currently, ghc gives a lexical error
  if I try to use that symbol anywhere, probably just since it's not an
  ASCII character.
 
 Hmm. On my keyboard it's Shift+4. Strange that it's not available on
 other keyboards. As far as I know that symbol means nothing
 particularly swedish. In fact, I have no idea what it means at all
 =)

It's a generic currency symbol (the X11 keysym is XK_currency). It
doesn't exist on a UK keyboard (where Shift-4 is the dollar sign).

In any case, using non-ASCII characters gives rise to encoding issues
(e.g. you have to be able to edit UTF-8 files).

-- 
Glynn Clements [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Sebastian Sylvan
On 11/18/05, Tomasz Zielonka [EMAIL PROTECTED] wrote:
 On Thu, Nov 17, 2005 at 06:56:09PM +0100, Sebastian Sylvan wrote:

  Some people do use it more often than I do, but I find that in most
  cases except simple pipelined functions it only makes the code
  harder to read.

 But this case is quite important, isn't it?

I'm not so sure it is, and you can almost always write it using ($)
without too much trouble. I really only ever use (.) for pretty simple
things like filter (not . null).

Again. I'm thinking () is a good operator. An intelligent editor
would pull them together a bit more to make it look even more like a
ring.
I could see myself using  and  for dot and cross products in
linear algebra, though, but I'm willing to sacrifice those operators
for the greater good :-)

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread John Meacham
I always fancied () as a synonym for 'mappend'
John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records

2005-11-18 Thread Ketil Malde
Fraser Wilson [EMAIL PROTECTED] writes:

Isn't there a potential for confusion with function
  composition (f . g)?

 Perhaps, but I always have spaces on either side when it's function
 composition.

Good for you.  Syntax that changes depending on spacing is my number
one gripe with the Haskell syntax.  And too many infix operators and
symbolic elements are on the list as well.

How about a pair of (magical, if necessary) functions called set and
get?  Letting you do something like

  x `set` first 4 `set` second foo
?

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Tomasz Zielonka
On Fri, Nov 18, 2005 at 12:21:09PM +0100, Sebastian Sylvan wrote:
 On 11/18/05, Tomasz Zielonka [EMAIL PROTECTED] wrote:
  On Thu, Nov 17, 2005 at 06:56:09PM +0100, Sebastian Sylvan wrote:
 
   Some people do use it more often than I do, but I find that in most
   cases except simple pipelined functions it only makes the code
   harder to read.
 
  But this case is quite important, isn't it?
 
 I'm not so sure it is, and you can almost always write it using ($)
 without too much trouble. I really only ever use (.) for pretty simple
 things like filter (not . null).

Try not to look as if you wanted to _remove_ the composition operator,
because that will make people angry (w...) :-)
We are talking about _renaming_ the composition, not removing it,
right?

If you removed it from the Prelude, most people would write their own
versions, with different names, and we rather don't want that.

Anyway, is it realistic to expect that people will rewrite their
programs to use the new operator? I thought that the new version of
Haskell will be mostly downwards compatible with Hashell 98?

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Sebastian Sylvan
On 11/18/05, Tomasz Zielonka [EMAIL PROTECTED] wrote:
 On Fri, Nov 18, 2005 at 12:21:09PM +0100, Sebastian Sylvan wrote:
  On 11/18/05, Tomasz Zielonka [EMAIL PROTECTED] wrote:
   On Thu, Nov 17, 2005 at 06:56:09PM +0100, Sebastian Sylvan wrote:
 
Some people do use it more often than I do, but I find that in most
cases except simple pipelined functions it only makes the code
harder to read.
  
   But this case is quite important, isn't it?
 
  I'm not so sure it is, and you can almost always write it using ($)
  without too much trouble. I really only ever use (.) for pretty simple
  things like filter (not . null).

 Try not to look as if you wanted to _remove_ the composition operator,
 because that will make people angry (w...) :-)
 We are talking about _renaming_ the composition, not removing it,
 right?

Yes. I just don't think it's used enough to warrant giving it one of
the best symbols.

 Anyway, is it realistic to expect that people will rewrite their
 programs to use the new operator? I thought that the new version of
 Haskell will be mostly downwards compatible with Hashell 98?

Well the records proposal is unlikely to go in Haskell 1.5 anyway, so
I'm mainly exercising wishful thinking here. In Haskell 2.0, which I
understand to be more of a complete make-over, backwards-compability
be damned!, this could be considered.

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread Benjamin Franksen
On Friday 18 November 2005 02:59, you wrote:
 On Nov 17, 2005, at 1:52 PM, Benjamin Franksen wrote:
  ...
  Yes, yes, yes. I'd rather use a different operator for record
  selection.
  For instance the colon (:). Yes, I know it is the 'cons' operator
  for a
  certain concrete data type that implements stacks (so called
  'lists'). However I am generally opposed to wasting good operator
  and function names as well as syntactic sugar of any kind on a
  /concrete/ data type,
  and especially not for stacks aka lists.

 Would you be happier if it were the yield operator for iterators?

 Yours lazily,

Ok, ok, I tend to forget that Haskell lists are lazy streams, not just 
simple stacks... which makes them indeed a /lot/ more useful than the 
corresponding data type in strict languages.

I still think all those nice short and meaningful names in the Prelude 
(map, filter, ...) should be type class members in some suitable 
standard collection library.

Ben
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-18 Thread John Meacham
On Fri, Nov 18, 2005 at 04:22:59PM +0100, Sebastian Sylvan wrote:
 Yes. I just don't think it's used enough to warrant giving it one of
 the best symbols.

 grep -o ' [-+.*/[EMAIL PROTECTED] ' GenUtil.hs | sort | uniq -c | sort -n
  1  $! 
  1  * 
  8  + 
 10  == 
 12  - 
 17  -- 
 30  . 
 31  $ 
 39  ++ 

one of the most common operators. I think experienced haskell programers
tend to use it a whole lot more often than beginning ones, and I am not
even a point-free advocate.

John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Joel Reymont

I second this motion! I rather like Simon's proposal.

On Nov 17, 2005, at 5:00 PM, Fraser Wilson wrote:


Yeah, I thought you might have tried that at some point :-)

I like http://research.microsoft.com/~simonpj/Haskell/records.html

cheers,
Fraser.

On 11/17/05, Joel Reymont [EMAIL PROTECTED]  wrote: Don't get me  
started, please :-). I tried making each field a

separate class but then needed to compose records of difference field
instances which led to HList which led to GHC eating up all my memory
and crashing, etc.

I can see where you are going but if I have 250 records with shared
fields then that's a whole lot of extra boiler plate code to marshall
between the functions with prefixes to the class method
implementations. The road to hell is paved with good intentions ;-).

Thanks for the tip, though.

On Nov 17, 2005, at 2:12 PM, Fraser Wilson wrote:

 To solve this problem I just made them all instances of a class
 with a gameId function.  Still, not ideal.


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Greg Woodhouse
Isn't there a potential for confusion with function composition (f . g)?

That being said, I like this idea (I just need to think it through a bit).Joel Reymont [EMAIL PROTECTED] wrote:
I second this motion! I rather like Simon's proposal.On Nov 17, 2005, at 5:00 PM, Fraser Wilson wrote: Yeah, I thought you might have tried that at some point :-) I like http://research.microsoft.com/~simonpj/Haskell/records.html cheers, Fraser.






===Gregory Woodhouse [EMAIL PROTECTED]
"Interaction is the mind-body problem of computing."
--Philip Wadler
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Sebastian Sylvan
On 11/17/05, Greg Woodhouse [EMAIL PROTECTED] wrote:
 Isn't there a potential for confusion with function composition (f . g)?

 That being said, I like this idea (I just need to think it through a bit).


I've been wanting this for ages. It's SO much better than the current
horribly broken records we have.
There could be confusion with function composition, but there's no
ambiguity (compositon have spaces around the dot, while record
accessors do not).
Personally I think that the dot is way to good of a symbol to be
wasted on function composition. I mean, how often do you really use
function composition in a way which doesn't obfuscate your code? I use
($) way more often than (.). Some people do use it more often than I
do, but I find that in most cases except simple pipelined functions
it only makes the code harder to read.
I'd rather function composition was left out of the prelude
alltogether (or defined as (#) or something).

Anyway. The current records system is a wart.



 Joel Reymont [EMAIL PROTECTED] wrote:
 I second this motion! I rather like Simon's proposal.

 On Nov 17, 2005, at 5:00 PM, Fraser Wilson wrote:

  Yeah, I thought you might have tried that at some point :-)
 
  I like
 http://research.microsoft.com/~simonpj/Haskell/records.html
 
  cheers,
  Fraser.










 ===
 Gregory Woodhouse  [EMAIL PROTECTED]


 Interaction is the mind-body problem of computing.

 --Philip Wadler



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Dimitry Golubovsky
Sebastian Sylvan wrote:

Personally I think that the dot is way to good of a symbol to be
wasted on function composition. I mean, how often do you really use
function composition in a way which doesn't obfuscate your code? I use
($) way more often than (.). Some people do use it more often than I

I found it useful to use (mainly for debugging purposes)

mapM (putStrLn . show) some list

if I want to print its elements each on a new line.

--
Dimitry Golubovsky

Anywhere on the Web
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Joel Reymont
So it sounds to me that momentum is building behind Simon PJ's  
proposal and that we are finally getting somewhere!


Now, when can we actually get this in GHC?

On Nov 17, 2005, at 5:56 PM, Sebastian Sylvan wrote:


I've been wanting this for ages. It's SO much better than the current
horribly broken records we have.


--
http://wagerlabs.com/





___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Chris Kuklewicz
Would the record system describe at
http://lambda-the-ultimate.org/node/view/1119
also be convertable into System Fw, GHC's existing, strongly-typeed
intermediate language. ?





On Thu, November 17, 2005 17:56, Sebastian Sylvan said:
 On 11/17/05, Greg Woodhouse [EMAIL PROTECTED] wrote:
 Isn't there a potential for confusion with function composition (f . g)?

 That being said, I like this idea (I just need to think it through a
 bit).


 I've been wanting this for ages. It's SO much better than the current
 horribly broken records we have.
 There could be confusion with function composition, but there's no
 ambiguity (compositon have spaces around the dot, while record
 accessors do not).
 Personally I think that the dot is way to good of a symbol to be
 wasted on function composition. I mean, how often do you really use
 function composition in a way which doesn't obfuscate your code? I use
 ($) way more often than (.). Some people do use it more often than I
 do, but I find that in most cases except simple pipelined functions
 it only makes the code harder to read.
 I'd rather function composition was left out of the prelude
 alltogether (or defined as (#) or something).

 Anyway. The current records system is a wart.



 Joel Reymont [EMAIL PROTECTED] wrote:
 I second this motion! I rather like Simon's proposal.

 On Nov 17, 2005, at 5:00 PM, Fraser Wilson wrote:

  Yeah, I thought you might have tried that at some point :-)
 
  I like
 http://research.microsoft.com/~simonpj/Haskell/records.html
 
  cheers,
  Fraser.










 == Gregory Woodhouse  [EMAIL PROTECTED]


 Interaction is the mind-body problem of computing.

 --Philip Wadler



 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe





 --
 Sebastian Sylvan
 +46(0)736-818655
 UIN: 44640862
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Cale Gibbard
Sebastian Sylvan wrote:

Personally I think that the dot is way to good of a symbol to be
wasted on function composition. I mean, how often do you really use
function composition in a way which doesn't obfuscate your code? I use
($) way more often than (.). Some people do use it more often than I

Function composition is a very important and fundamental operation on
functions, and I use it all the time. Haskell is supposed to be a
functional language. I'd vote against any motion to make it less
convenient. Of course, it really shouldn't be (.) but a small circle
centred on the line, which isn't on ordinary keyboards. (°) looks
closer, but is much less convenient to type. (I need to type
Compose 0 ^ in order to get that character.) Spelling it as (.)
really is the best easy-to-type approximation.

 - Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Fraser Wilson
On 11/17/05, Greg Woodhouse [EMAIL PROTECTED] wrote:
Isn't there a potential for confusion with function composition (f . g)?
Perhaps, but I always have spaces on either side when it's function composition. Isn't there already an ambiguity?

-- I bet there's a quicker way to do this ...
module M where data M a = M a deriving (Show)

data T a = T a deriving (Show)
module M.T where f = (+1)
 
import M
import qualified M.T

f = (*2)
v1 = M . T . f $ 5
v2 = M.T.f $ 5

main = do { print v1; print v2; return () }

Fraser.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Jon Fairbairn
On 2005-11-17 at 13:21EST Cale Gibbard wrote:
 Sebastian Sylvan wrote:
 
 Personally I think that the dot is way to good of a symbol to be
 wasted on function composition. I mean, how often do you really use
 function composition in a way which doesn't obfuscate your code? I use
 ($) way more often than (.). Some people do use it more often than I
 
 Function composition is a very important and fundamental operation on
 functions, and I use it all the time. Haskell is supposed to be a
 functional language. I'd vote against any motion to make it less
 convenient.

Hear hear.

 Of course, it really shouldn't be (.) but a small circle
 centred on the line, which isn't on ordinary keyboards. (°) looks
 closer, but is much less convenient to type. (I need to type
 Compose 0 ^ in order to get that character.) Spelling it as (.)
 really is the best easy-to-type approximation.

Ought to be ∘, unicode 0x2218, but without defining some
keyboard macros, that's even harder to type. On the other
hand, I could define ctrl-. as (ucs-insert 2218), and then
it would be no harder to type than . 



-- 
Jón Fairbairn  Jon.Fairbairn at cl.cam.ac.uk


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Benjamin Franksen
On Thursday 17 November 2005 19:21, Cale Gibbard wrote:
 Sebastian Sylvan wrote:
 Personally I think that the dot is way to good of a symbol to be
 wasted on function composition. I mean, how often do you really
  use function composition in a way which doesn't obfuscate your
  code? I use ($) way more often than (.). Some people do use it more
  often than I

 Function composition is a very important and fundamental operation on
 functions, and I use it all the time. Haskell is supposed to be a
 functional language. I'd vote against any motion to make it less
 convenient. Of course, it really shouldn't be (.) but a small circle 
 centred on the line, which isn't on ordinary keyboards. (°) looks
 closer, but is much less convenient to type. (I need to type
 Compose 0 ^ in order to get that character.) Spelling it as (.)
 really is the best easy-to-type approximation.

Yes, yes, yes. I'd rather use a different operator for record selection. 
For instance the colon (:). Yes, I know it is the 'cons' operator for a 
certain concrete data type that implements stacks (so called 'lists'). 
However I am generally opposed to wasting good operator and function 
names as well as syntactic sugar of any kind on a /concrete/ data type, 
and especially not for stacks aka lists.

For a hypothetical Haskell2 I'd propose to get rid of all special 'list' 
constructs and re-use the good symbols and names for /abstract/ 
interfaces to sequences and collections resp. (in case of the colon) 
for record selection.

Just my 2 cent.

Ben
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Cale Gibbard
On 17/11/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 11/17/05, Greg Woodhouse [EMAIL PROTECTED] wrote:
  Isn't there a potential for confusion with function composition (f . g)?
 
  That being said, I like this idea (I just need to think it through a bit).
 

 I've been wanting this for ages. It's SO much better than the current
 horribly broken records we have.
 There could be confusion with function composition, but there's no
 ambiguity (compositon have spaces around the dot, while record
 accessors do not).
 Personally I think that the dot is way to good of a symbol to be
 wasted on function composition. I mean, how often do you really use
 function composition in a way which doesn't obfuscate your code? I use
 ($) way more often than (.). Some people do use it more often than I
 do, but I find that in most cases except simple pipelined functions
 it only makes the code harder to read.
 I'd rather function composition was left out of the prelude
 alltogether (or defined as (#) or something).

 Anyway. The current records system is a wart.


Actually, I didn't mention this in the other post, but why not the
other way around? Make record selection (#) or (!) (though the latter
gets in the way of array access), and leave (.) for function
composition. Personally, I'd like something which looked like an arrow
for record selection, but most of the good 2-character ones are
unavailable. (~) is a bit hard to type and looks wrong in some fonts.
There's a triangle which is not taken, and isn't so hard to type
(|).

I never really understood the attachment to (.) for record selection.
There's no reason that we have to make things look like Java and C.

Another option is to make application of a label to a record mean
projection, somewhat like things currently are, though since labels
aren't really functions anymore that is potentially confusing.

 - Cale
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Sebastian Sylvan
On 11/17/05, Cale Gibbard [EMAIL PROTECTED] wrote:
 On 17/11/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  On 11/17/05, Greg Woodhouse [EMAIL PROTECTED] wrote:
   Isn't there a potential for confusion with function composition (f . g)?
  
   That being said, I like this idea (I just need to think it through a bit).
  
 
  I've been wanting this for ages. It's SO much better than the current
  horribly broken records we have.
  There could be confusion with function composition, but there's no
  ambiguity (compositon have spaces around the dot, while record
  accessors do not).
  Personally I think that the dot is way to good of a symbol to be
  wasted on function composition. I mean, how often do you really use
  function composition in a way which doesn't obfuscate your code? I use
  ($) way more often than (.). Some people do use it more often than I
  do, but I find that in most cases except simple pipelined functions
  it only makes the code harder to read.
  I'd rather function composition was left out of the prelude
  alltogether (or defined as (#) or something).
 
  Anyway. The current records system is a wart.
 

 Actually, I didn't mention this in the other post, but why not the
 other way around? Make record selection (#) or (!) (though the latter
 gets in the way of array access), and leave (.) for function
 composition. Personally, I'd like something which looked like an arrow
 for record selection, but most of the good 2-character ones are
 unavailable. (~) is a bit hard to type and looks wrong in some fonts.
 There's a triangle which is not taken, and isn't so hard to type
 (|).

 I never really understood the attachment to (.) for record selection.
 There's no reason that we have to make things look like Java and C.

This is going to be highly fuzzy and completely subjective. Here it goes.

I find that for selections (records, or qualified modules etc.) I want
the operator to be small and so that the important word groups
become the module or the record.
When I read the following two variants
myPoint#x
myPoint.x

I definatly prefer the latter. In the first one the operator is so
large that it makes myPoint and x blend together as you read it
(step away from the monitor and squint and you'll see what I mean),
whereas in the second example the operator is small and makes the two
operands naturally separate slightly when reading it, which makes it
easier to tell which identifier is accessed. Also, it's certainly not
a BAD thing if Haskell uses the same operators as other languages.

With function composition, though, the operator is just as important
to identify when reading as the operands are. So I don't think a big
operator is a problem there - likewise I have no problems with ($)
being large.

How about (¤)? It looks like a ring to me, I'm not sure where that's
located on a EN keyboard, but it's not terribly inconvenient on my SE
keyboard. f ¤ g looks better than f . g for function composition, if
you ask me.


That's my subjective view on why the dot-operator is so darn nice, anyway.

Oh and to answer to your other post. I realise that function
composition is a fundamental operation, but it's so fundamental that
it's quite useless for most real-world cases unless your willing to
seriously ubfuscate your code.
IMO it really only works well for simple chains like foo . bar .
oof . rab but as soon as you start working with functions that take
more parameters it starts looking very unreadable and you'd be better
off to just use $ or write out paranthesis and apply arguments
explicitly, or better yet, introduce some temporary descriptive
variables in a let or where clause.

It's a matter of personal preference, but I certainly haven't found it
used enough to warrant giving it perhaps the best symbol on the
keyboard.


/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Greg Woodhouse


--- Cale Gibbard [EMAIL PROTECTED] wrote:

 Actually, I didn't mention this in the other post, but why not the
 other way around? Make record selection (#) or (!) (though the latter
 gets in the way of array access), and leave (.) for function
 composition. 

Actually, the fact that (!) is the array selector makes it all the more
attractive as a record selector. (It does make you wonder if a record
isn't a kind of a typed associative array, though...)

 Personally, I'd like something which looked like an
 arrow
 for record selection, but most of the good 2-character ones are
 unavailable. (~) is a bit hard to type and looks wrong in some
 fonts.

Well, yeah, but the arrows have such a fundamentally different meaning
in Haskell. (I thought of that one, too).

 There's a triangle which is not taken, and isn't so hard to type
 (|).

If we're not careful, though, Haskell will end up looking like APL.
 
 I never really understood the attachment to (.) for record selection.
 There's no reason that we have to make things look like Java and C.
 
 Another option is to make application of a label to a record mean
 projection, somewhat like things currently are, though since labels
 aren't really functions anymore that is potentially confusing.
 

Actually, I thought of that, too, or rather something like

get label record

or

get record label

(I haven't made up my mind which way the currying makes more sense. Do
you have a generic function for getting records with a certain label,
or do you apply get label, tget the field with this label, to
record?)

  - Cale
 



===
Gregory Woodhouse  [EMAIL PROTECTED]


Interaction is the mind-body problem of computing.

--Philip Wadler











___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Cale Gibbard
On 17/11/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 11/17/05, Cale Gibbard [EMAIL PROTECTED] wrote:
  On 17/11/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
   On 11/17/05, Greg Woodhouse [EMAIL PROTECTED] wrote:
Isn't there a potential for confusion with function composition (f . g)?
   
That being said, I like this idea (I just need to think it through a 
bit).
   
  
   I've been wanting this for ages. It's SO much better than the current
   horribly broken records we have.
   There could be confusion with function composition, but there's no
   ambiguity (compositon have spaces around the dot, while record
   accessors do not).
   Personally I think that the dot is way to good of a symbol to be
   wasted on function composition. I mean, how often do you really use
   function composition in a way which doesn't obfuscate your code? I use
   ($) way more often than (.). Some people do use it more often than I
   do, but I find that in most cases except simple pipelined functions
   it only makes the code harder to read.
   I'd rather function composition was left out of the prelude
   alltogether (or defined as (#) or something).
  
   Anyway. The current records system is a wart.
  
 
  Actually, I didn't mention this in the other post, but why not the
  other way around? Make record selection (#) or (!) (though the latter
  gets in the way of array access), and leave (.) for function
  composition. Personally, I'd like something which looked like an arrow
  for record selection, but most of the good 2-character ones are
  unavailable. (~) is a bit hard to type and looks wrong in some fonts.
  There's a triangle which is not taken, and isn't so hard to type
  (|).
 
  I never really understood the attachment to (.) for record selection.
  There's no reason that we have to make things look like Java and C.

 This is going to be highly fuzzy and completely subjective. Here it goes.

 I find that for selections (records, or qualified modules etc.) I want
 the operator to be small and so that the important word groups
 become the module or the record.
 When I read the following two variants
 myPoint#x
 myPoint.x

I think both of those look crowded -- smashing operator punctuation up
against symbols basically never looks good to me. The right amount of
spacing isn't generally available without proper typesetting, but a
full space is a lot closer than no space at all.

Why not myPoint # x and myPoint . x?


 I definatly prefer the latter. In the first one the operator is so
 large that it makes myPoint and x blend together as you read it
 (step away from the monitor and squint and you'll see what I mean),
 whereas in the second example the operator is small and makes the two
 operands naturally separate slightly when reading it, which makes it
 easier to tell which identifier is accessed. Also, it's certainly not
 a BAD thing if Haskell uses the same operators as other languages.

 With function composition, though, the operator is just as important
 to identify when reading as the operands are. So I don't think a big
 operator is a problem there - likewise I have no problems with ($)
 being large.

 How about (¤)? It looks like a ring to me, I'm not sure where that's
 located on a EN keyboard, but it's not terribly inconvenient on my SE
 keyboard. f ¤ g looks better than f . g for function composition, if
 you ask me.

That symbol actually does look better, but isn't on any English
keyboards to the best of my knowledge. I can get it in my setup with
compose-key o x, but not many people have a compose key assigned.
Also, this may just be a bug, but currently, ghc gives a lexical error
if I try to use that symbol anywhere, probably just since it's not an
ASCII character.

 That's my subjective view on why the dot-operator is so darn nice, anyway.

 Oh and to answer to your other post. I realise that function
 composition is a fundamental operation, but it's so fundamental that
 it's quite useless for most real-world cases unless your willing to
 seriously ubfuscate your code.

I disagree, there are plenty of cases where it's just what you want,
and saves you from introducing a lambda term for nothing. This occurs
very often in parameters to higher order functions. A simple example
would be something like filter (not . null), or any ((`elem`
consumers) . schVertex). More sophisticated examples come up all the
time, and often the functions being composed have some parameters
applied to them. I disagree that it's just for obfuscation. Using
function composition puts emphasis on the manipulation of functions
rather than on the manipulation of the elements those functions act
on, and quite often in a functional language that's just what you
want.

 IMO it really only works well for simple chains like foo . bar .
 oof . rab but as soon as you start working with functions that take
 more parameters it starts looking very unreadable and you'd be better
 off to just use $ or write out paranthesis 

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Cale Gibbard
On 17/11/05, Benjamin Franksen [EMAIL PROTECTED] wrote:
 On Thursday 17 November 2005 19:21, Cale Gibbard wrote:
  Sebastian Sylvan wrote:
  Personally I think that the dot is way to good of a symbol to be
  wasted on function composition. I mean, how often do you really
   use function composition in a way which doesn't obfuscate your
   code? I use ($) way more often than (.). Some people do use it more
   often than I
 
  Function composition is a very important and fundamental operation on
  functions, and I use it all the time. Haskell is supposed to be a
  functional language. I'd vote against any motion to make it less
  convenient. Of course, it really shouldn't be (.) but a small circle
  centred on the line, which isn't on ordinary keyboards. (°) looks
  closer, but is much less convenient to type. (I need to type
  Compose 0 ^ in order to get that character.) Spelling it as (.)
  really is the best easy-to-type approximation.

 Yes, yes, yes. I'd rather use a different operator for record selection.
 For instance the colon (:). Yes, I know it is the 'cons' operator for a
 certain concrete data type that implements stacks (so called 'lists').
 However I am generally opposed to wasting good operator and function
 names as well as syntactic sugar of any kind on a /concrete/ data type,
 and especially not for stacks aka lists.

However, the way things are currently, all symbols starting with ':'
are constructors of concrete data types, as that's how infix data
constructors are distinguished. Also, I must point out that lists are
a pretty important structure in lazy functional programming, taking
the place of loops in an imperative language, and their importance
shouldn't be taken so lightly. Given how much they are used, giving
them a little syntax sugar and good looking data constructors doesn't
seem all that far off. On the other hand, I would like to see list
comprehensions generalised to monad comprehensions again.

 For a hypothetical Haskell2 I'd propose to get rid of all special 'list'
 constructs and re-use the good symbols and names for /abstract/
 interfaces to sequences and collections resp. (in case of the colon)
 for record selection.

However, you can't abstract data constructors. If cons was abstracted,
then you couldn't use it in pattern matching, which is problematic.


 Just my 2 cent.

 Ben
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Sebastian Sylvan
On 11/17/05, Cale Gibbard [EMAIL PROTECTED] wrote:
 On 17/11/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
  On 11/17/05, Cale Gibbard [EMAIL PROTECTED] wrote:
   On 17/11/05, Sebastian Sylvan [EMAIL PROTECTED] wrote:
On 11/17/05, Greg Woodhouse [EMAIL PROTECTED] wrote:
 Isn't there a potential for confusion with function composition (f . 
 g)?

 That being said, I like this idea (I just need to think it through a 
 bit).

   
I've been wanting this for ages. It's SO much better than the current
horribly broken records we have.
There could be confusion with function composition, but there's no
ambiguity (compositon have spaces around the dot, while record
accessors do not).
Personally I think that the dot is way to good of a symbol to be
wasted on function composition. I mean, how often do you really use
function composition in a way which doesn't obfuscate your code? I use
($) way more often than (.). Some people do use it more often than I
do, but I find that in most cases except simple pipelined functions
it only makes the code harder to read.
I'd rather function composition was left out of the prelude
alltogether (or defined as (#) or something).
   
Anyway. The current records system is a wart.
   
  
   Actually, I didn't mention this in the other post, but why not the
   other way around? Make record selection (#) or (!) (though the latter
   gets in the way of array access), and leave (.) for function
   composition. Personally, I'd like something which looked like an arrow
   for record selection, but most of the good 2-character ones are
   unavailable. (~) is a bit hard to type and looks wrong in some fonts.
   There's a triangle which is not taken, and isn't so hard to type
   (|).
  
   I never really understood the attachment to (.) for record selection.
   There's no reason that we have to make things look like Java and C.
 
  This is going to be highly fuzzy and completely subjective. Here it goes.
 
  I find that for selections (records, or qualified modules etc.) I want
  the operator to be small and so that the important word groups
  become the module or the record.
  When I read the following two variants
  myPoint#x
  myPoint.x

 I think both of those look crowded -- smashing operator punctuation up
 against symbols basically never looks good to me. The right amount of
 spacing isn't generally available without proper typesetting, but a
 full space is a lot closer than no space at all.

 Why not myPoint # x and myPoint . x?


Well, again this is just preference, but to me I'd like selectors to
not have space between the record and the label, they still need to be
connected, but with a symbol which is small enought to help you
easily see what's what.

 
  I definatly prefer the latter. In the first one the operator is so
  large that it makes myPoint and x blend together as you read it
  (step away from the monitor and squint and you'll see what I mean),
  whereas in the second example the operator is small and makes the two
  operands naturally separate slightly when reading it, which makes it
  easier to tell which identifier is accessed. Also, it's certainly not
  a BAD thing if Haskell uses the same operators as other languages.
 
  With function composition, though, the operator is just as important
  to identify when reading as the operands are. So I don't think a big
  operator is a problem there - likewise I have no problems with ($)
  being large.
 
  How about (¤)? It looks like a ring to me, I'm not sure where that's
  located on a EN keyboard, but it's not terribly inconvenient on my SE
  keyboard. f ¤ g looks better than f . g for function composition, if
  you ask me.
 
 That symbol actually does look better, but isn't on any English
 keyboards to the best of my knowledge. I can get it in my setup with
 compose-key o x, but not many people have a compose key assigned.
 Also, this may just be a bug, but currently, ghc gives a lexical error
 if I try to use that symbol anywhere, probably just since it's not an
 ASCII character.

Hmm. On my keyboard it's Shift+4. Strange that it's not available on
other keyboards. As far as I know that symbol means nothing
particularly swedish. In fact, I have no idea what it means at all
=)

  That's my subjective view on why the dot-operator is so darn nice, anyway.
 
  Oh and to answer to your other post. I realise that function
  composition is a fundamental operation, but it's so fundamental that
  it's quite useless for most real-world cases unless your willing to
  seriously ubfuscate your code.

 I disagree, there are plenty of cases where it's just what you want,
 and saves you from introducing a lambda term for nothing. This occurs
 very often in parameters to higher order functions. A simple example
 would be something like filter (not . null), or any ((`elem`
 consumers) . schVertex). More sophisticated examples come up all the
 time, and often 

Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread John Meacham
another thing is that for any record syntax, we would want higher order
versions of the selection, setting, and updating routines. A quick
perusal of my source code shows over half my uses of record selectors
are in a higher order fashion. (which need to be generated with DrIFT
with the current syntax)

I mean something like 

map (.foo) xs
to pull all the 'foo' fields out of xs.  (using made up syntax)

or 

map (foo_s 3) xs

to set all the foo fields to 3. (using DrIFT syntax)


John

-- 
John Meacham - ⑆repetae.net⑆john⑈ 
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Jan-Willem Maessen


On Nov 17, 2005, at 1:52 PM, Benjamin Franksen wrote:

...
Yes, yes, yes. I'd rather use a different operator for record  
selection.
For instance the colon (:). Yes, I know it is the 'cons' operator  
for a

certain concrete data type that implements stacks (so called 'lists').
However I am generally opposed to wasting good operator and function
names as well as syntactic sugar of any kind on a /concrete/ data  
type,

and especially not for stacks aka lists.


Would you be happier if it were the yield operator for iterators?

Yours lazily,

Jan-Willem Maessen



Just my 2 cent.

Ben
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread David Menendez
Chris Kuklewicz writes:

 Would the record system describe at
 http://lambda-the-ultimate.org/node/view/1119
 also be convertable into System Fw, GHC's existing, strongly-typeed
 intermediate language. ?

Probably. Daan's current implementation uses MLF, which I believe is
system F implemented for ML.

(We're talking about the system in Daan Leijen's paper, Extensible
Records With Scoped Labels. Good stuff.)
-- 
David Menendez [EMAIL PROTECTED] | In this house, we obey the laws
http://www.eyrie.org/~zednenem  |of thermodynamics!
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Sebastian Sylvan
On 11/18/05, John Meacham [EMAIL PROTECTED] wrote:
 another thing is that for any record syntax, we would want higher order
 versions of the selection, setting, and updating routines. A quick
 perusal of my source code shows over half my uses of record selectors
 are in a higher order fashion. (which need to be generated with DrIFT
 with the current syntax)

 I mean something like

 map (.foo) xs
 to pull all the 'foo' fields out of xs.  (using made up syntax)

Well I suppose this is just a section on the selection operator?

 map (foo_s 3) xs

This is trickier I think. I think I can live with map (\r - {r | s =
3}), though.


--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Tomasz Zielonka
On Fri, Nov 18, 2005 at 07:32:53AM +0100, Sebastian Sylvan wrote:
 On 11/18/05, John Meacham [EMAIL PROTECTED] wrote:
  map (.foo) xs
  to pull all the 'foo' fields out of xs.  (using made up syntax)
 
 Well I suppose this is just a section on the selection operator?

So field labels are first-class citizens? Great!

  map (foo_s 3) xs
 
 This is trickier I think. I think I can live with map (\r - {r | s =
 3}), though.

I think this special case could be treated specially, for example
(\r - {r | s = 3})
could be equivalent to
{|s = 3}

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Records (was Re: [Haskell] Improvements to GHC)

2005-11-17 Thread Tomasz Zielonka
On Thu, Nov 17, 2005 at 06:56:09PM +0100, Sebastian Sylvan wrote:
 Personally I think that the dot is way to good of a symbol to be
 wasted on function composition.

 I mean, how often do you really use function composition in a way
 which doesn't obfuscate your code?

I just checked in two recent projects, and it's about one (.) in 100
lines of code. I wanted to disagree with you, but in the end I could
accept pressing more keys when I wanted function composition, especially
if I got something in return.

BTW, I think there was some tool to calculate various metrics on Haskell
code. It would be interesting to make some graphs showing how often you
use various features of Haskell, how it changed with time.

 I use ($) way more often than (.).

Me too, measurement shows it's about four times more often. However,
I like my uses of (.) much more than uses of ($). I often turn $'s
into parentheses, because I feel it looks better this way. Of course,
there are cases where $ is indispensable.

 Some people do use it more often than I do, but I find that in most
 cases except simple pipelined functions it only makes the code
 harder to read.

But this case is quite important, isn't it?

Best regards
Tomasz
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe