RE: ANNOUNCE: GHC version 7.2.1 - {-# LANGUAGE NoTraditionalRecordSyntax #-}

2012-03-27 Thread Simon Peyton-Jones
ghci -XNoTraditionalRecordSyntax does not complain of unsupported extensions 
for me.
 
The flag appears to just disable record construction and update syntax, and 
record patterns, and record syntax in GADT declarations.  It has probably never 
been used.

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-
| users-boun...@haskell.org] On Behalf Of AntC
| Sent: 26 March 2012 23:47
| To: glasgow-haskell-users@haskell.org
| Subject: Re: ANNOUNCE: GHC version 7.2.1 - {-# LANGUAGE
| NoTraditionalRecordSyntax #-}
| 
| 
| Ian Lynagh igloo at earth.li writes:
| 
| =
|  The (Interactive) Glasgow Haskell Compiler -- version 7.2.1
| =
| 
| Ticket #3356 claims that {-# LANGUAGE NoTraditionalRecordSyntax #-} was
| implemented in 7.2.1.
| 
| But GHCi v7.2.1 complains Unsupported extension: NoTraditionalRecordSyntax.
| 
| What (if anything) actually got implemented?
| 
| Is/was the plan to be able to selectively 'prune' bits of record syntax? or
| just to completely banish anything with curly brackets {and their contents}
| from patterns, expressions and data declarations?
| 
| I ask because I'd like to raise a ticket for
| http://hackage.haskell.org/trac/ghc/wiki/Records/DeclaredOverloadedRecordFiel
| ds
| /NoMonoRecordFields -- that is, to enable declaring within the same module
| multiple record types with the same field name.
| 
| Of course it will also help when declaring the same field name in different
| (but imported) modules.
| 
| Avoiding generating the (monomorphic) field selector function is a modest
| step towards freeing up the namespace, without in any way pre-judging how the
| 'narrow namespace issue' might get addressed.
| 
| AntC
| 
| 
| 
| 
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC version 7.2.1 - {-# LANGUAGE NoTraditionalRecordSyntax #-}

2012-03-27 Thread Ian Lynagh
On Mon, Mar 26, 2012 at 10:47:14PM +, AntC wrote:

 Ticket #3356 claims that {-# LANGUAGE NoTraditionalRecordSyntax #-} was 
 implemented in 7.2.1.
 
 But GHCi v7.2.1 complains Unsupported extension: NoTraditionalRecordSyntax.
 
 What (if anything) actually got implemented?

It was implemented in 7.4.1.


Thanks
Ian


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users



Re: ANNOUNCE: GHC version 7.2.1 - {-#LANGUAGE NoTraditionalRecordSyntax#-}

2012-03-27 Thread AntC
Ian Lynagh igloo at earth.li writes:

 
 On Mon, Mar 26, 2012 at 10:47:14PM +, AntC wrote:
 
  Ticket #3356 claims that {-# LANGUAGE NoTraditionalRecordSyntax #-} was 
  implemented in 7.2.1.
  
  But GHCi v7.2.1 complains Unsupported extension: 
NoTraditionalRecordSyntax.
  
  What (if anything) actually got implemented?

 ghci -XNoTraditionalRecordSyntax does not complain of unsupported extensions 
 for me.
 ...
 Simon
 
 It was implemented in 7.4.1.
 
 Thanks
 Ian
 
Thank you Simon and Ian (and apologies for first posting to the Haskell list).

So I'll upgrade to 7.4, and play with it.

And post a ticket for the more modest idea of suppressing the (monomorphic) 
field selector function.

AntC




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: ANNOUNCE: GHC version 7.2.1 - {-#LANGUAGE NoTraditionalRecordSyntax#-}

2012-03-27 Thread AntC
Simon Peyton-Jones simonpj at microsoft.com writes:

 
 ghci -XNoTraditionalRecordSyntax does not complain of unsupported extensions 
for me.

OK, it's effective in v7.4.1, as Ian says.

 
 The flag appears to just disable record construction and update syntax, and 
 record patterns, and record syntax in GADT declarations.

For the record(!) it also suppresses record syntax in ordinary data 
declarations. So it 'solves' the namespacing issue by not allowing field names 
at all.

No curly brackets, no field names nowhere! Everything has to be positional.

  It has probably never been used.
 

Yes, the pruning is _too_ radical, the tree withered away.

AntC




___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Records in Haskell - updating Higher-Ranked fields

2012-03-27 Thread AntC
Gábor Lehel illissius at gmail.com writes:
 
 ..., but DORF actually requires less type system magic than
 SORF, and also already has a working prototype implementation, ...
 
 ... My main complaint against DORF is
 that having to write fieldLabel declarations for every field you want
 to use is onerous. ...
 

(Here's a possible way to reduce the need for declarations,
 for non-sharing fields; also avoid the fieldLabel new decl.)

SPJ introduced some fancy type-handling for higher-ranked fields. But still it 
only helped in accessing a H-R field, not updating it.

If we accept that updating H-R fields in liberated-namespace records is not 
possible, can we simplify the implementation? I think so. Here's what I'd call 
a well-principled work-round (not a hack, but then neither a solution).

(I'm showing it in DORF-like style, but I think it would work equally in SORF 
style with Stringy Kinds. The advantage of showing DORF is that we can try it -
- which I've done.)

You write:
data HR = HR{ objectId :: ObjectId  -- type Pun
, rev :: forall a. [a] - [a] } -- SPJ's example
 sharing (ObjectId) deriving (...)  -- new syntax
 -- this decl is not sharing `rev`, so no further code needed

 -- HR is sharing objectId, so you need a field Label in scope:
 -- probably you're already declaring newtypes/data
newtype ObjectId = ObjectId Int -- declaring a field
  deriving (Has, ... )  -- `Has` makes it a label

Field access can be polymorphic:
f :: HR - ([Bool], [Char])
f r = (r.rev [True], r.rev hello)

Record update looks like:
... myHR{ rev = Rev reverse } ...   -- annoying pun
But perhaps we could support sugar for it:
... myHR{ Rev reverse } ... -- fewer keystrokes!

The HR decl desugars to:
newtype Rev = Rev (forall a. [a] - [a])-- newtype punning
data HR = HR{ objectId :: ObjectId, rev :: Rev }
rev :: HR - (forall a. [a] - [a]) -- monotype field selector
rev r = let (Rev fn) = get r (undefined :: Rev) in fn
instance Has HR Revwhere
get HR{ rev } _ = rev   -- have to wrap the fn
set (Rev fn) HR{ .. } = HR{ rev = (Rev fn) }
type instance FieldTy HR Rev = Rev  -- have to wrap this
-- else update don't work

So I've simplified `Has` to two type arguments (like the more naieve form SPJ 
considers then rejects). And used the field's type itself as the index (so 
that we're punning on the field name):
class Has r fld   where
get :: r - fld - FieldTy r fld
set :: fld - r - SetTy r fld  -- for type change update

For the record type's `sharing` fields we desugar to:
instance Has HR ObjectId   where
get HR{ objectId } _ = objectId -- yeah dull, dull
set x HR{ .. }   = HR{ objectId = x, .. }

and the `deriving (Has)` on the newtype or data desugars to:
objectId :: {Has r ObjectId} = r - ObjectId   -- overloaded record 
objectId r = get r (undefined :: ObjectId)  -- selector
type instance FieldTy r ObjectId = ObjectId -- not parametric

AntC


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users