Re: GHC support for the new record package

2015-01-24 Thread Simon Marlow

On 23/01/15 23:41, Simon Peyton Jones wrote:

| I just
| noticed that it effectively gives us a syntax for identifier-like Symbol
| singletons, which could be useful in completely different contexts

Indeed so.  I have written a major increment to
https://ghc.haskell.org/trac/ghc/wiki/Records/OverloadedRecordFields/Redesign
which people reading this thread may find interesting.  Look for Plan B.

For the first time I think I can see a nice, simple, elegant, orthogonal story.


Cunning, and very general.  I like it.

Cheers,
Simon

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


SPARC NCG, how to debug load isn issue.

2015-01-24 Thread Karel Gardas


Folks,

from time to time I'm attempting to resurrect SPARC NCG. It looks like 
it's off by default since 7.4? release and I feel it's kind of pity. 
I've been able to hack it on 7.6.x and make it functional. I failed on 
7.8 and later. Double float load was broken there.


Now, I'm attempting on fairly recent GHC HEAD as of Jan 17 and I do have 
problem with illegal isn generated into the binary. This is caused by LD 
II64 ... Instr to be translated to SPARC ldd addr,g1 where g1 reg is 
not even, but odd and this fails as spec. says:



The load doubleword integer instructions (LDD, LDDA) move a doubleword
from memory into an r register pair. The more significant word at the
effective memory address is moved into the even r register. The less
significant word (at the effective memory address + 4) is moved into the 
following

odd r register. (Note that a load doubleword with rd = 0 modifies
only r[1].) The least significant bit of the rd field is unused and 
should be set

to zero by software. An attempt to execute a load doubleword instruction
that refers to a mis-aligned (odd) destination register number may cause an
illegal_instruction trap.


I've found out that the problematic source code is HeapStackCheck.cmm 
and the problematic piece is:


if (Capability_context_switch(MyCapability()) != 0 :: CInt ||
Capability_interrupt(MyCapability())  != 0 :: CInt ||
(StgTSO_alloc_limit(CurrentTSO) `lt` (0::I64) 
 (TO_W_(StgTSO_flags(CurrentTSO))  TSO_ALLOC_LIMIT) != 
0)) {

ret = ThreadYielding;
goto sched;


This (0::I64) causes it. So that's the problem description. Now I'm 
attempting to debug it a little bit to find out where the LD II64 Instr 
is generated and I'm not able to find single place which would looks 
familiar with asm I get here:


.Lcq:
ld  [%i1+812],%g1
ldd [%g1+64],%g1
cmp %g1,0
bge .Lcs
nop
b   .Lcr
nop



more importantly when I look into sparc's version on mkLoadInstr, I 
don't see any way how it may generate LD II64:


sparc_mkLoadInstr dflags reg _ slot
  = let platform = targetPlatform dflags
off  = spillSlotToOffset dflags slot
off_w   = 1 + (off `div` 4)
sz  = case targetClassOfReg platform reg of
RcInteger - II32
RcFloat   - FF32
RcDouble  - FF64
_ - panic sparc_mkLoadInstr

in LD sz (fpRel (- off_w)) reg


In whole SPARC NCG I've found the only place which clearly uses LD II64 
and this is in Gen32.hs for loading literal float into reg:


getRegister (CmmLit (CmmFloat d W64)) = do
lbl - getNewLabelNat
tmp - getNewRegNat II32
let code dst = toOL [
LDATA ReadOnlyData $ Statics lbl
 [CmmStaticLit (CmmFloat d W64)],
SETHI (HI (ImmCLbl lbl)) tmp,
LD II64 (AddrRegImm tmp (LO (ImmCLbl lbl))) dst]
return (Any FF64 code)


It's interesting but also iselExpr64 which should be probably here for 
manipulating 64bit data on 32bit platform, so even this is using pairs 
of LD II32 Instrs instead of single LD II64


So I'm kind of out of idea where the LD II64 gets in the flow and is 
later translated into ldd with problematic reg.


Do you have any idea how to debug this issue? Or do you have any idea 
where to read more about general structure of NCG, I've already seen 
https://ghc.haskell.org/trac/ghc/wiki/Commentary/Compiler/Backends/NCG 
-- but this is kind of dated...


Thanks for any idea how to proceed!
Karel

___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: GHC support for the new record package

2015-01-24 Thread Konstantine Rybnikov
May I suggest something for a syntax (as an option, sorry if it's silly or
not related)? I really don't like neither @ or # because they seem too
hacky, meanwhile GHC already has an accessor syntax with braces { and },
so, might it be an option to have something like:

```
data Foo = Foo { val :: Int }
data Bar = Bar { foo :: Foo }

main = do
  let bar = Bar (Foo 10)
  print bar{foo{val}}
  let bar' = bar{foo{val}=10}
  return ()

```

I think this syntax is 100% understandable for a newbie. Not sure how is
it related to lenses though.

What do you think?
If the level of complaints I received when I stole (#) for use in lens is
any indication, er.. it is in very wide use. It was by far the most
contentious operator I grabbed. ;)

It seems to me that I'd not be in a hurry to both break existing code and
pay a long term syntactic cost when we have options on the table that don't
require either, the magic Field module approach that both Eric and I
appear to have arrived at independently side-steps this issue nicely and
appears to result in a better user experience.

Keep in mind, one source of objections to operator-based sigils is that if
you put an sigil at the start of a lens the tax isn't one character but
two, there is a space you now need to avoid (.#) when chaining these
things. foo.bar vs. #foo . #bar and the latter will always be uglier.

The `import Field (...)` approach results in users never having to pay more
syntactically than with options they have available to them now, and being
class based is even beneficial to folks who don't use Nikita's records.

-Edward

On Fri, Jan 23, 2015 at 5:47 PM, Greg Weber g...@gregweber.info wrote:

 If we only add syntax when the language extension is used then we are not
 clobbering everyone. # is not that common of an operator. I would much
 rather upset a few people by taking that operator back when they opt-in to
 turning the extension on than having a worse records implementation.

 On Fri, Jan 23, 2015 at 2:23 PM, Edward Kmett ekm...@gmail.com wrote:


 On Fri, Jan 23, 2015 at 5:06 PM, Adam Gundry a...@well-typed.com wrote:

 Thanks for the feedback, Iavor!

 On 23/01/15 19:30, Iavor Diatchki wrote:
  2. I would propose that we simplify things further, and provide just
 one
  class for overloading:
 
  class Field (name :: Symbol)
  rec   rec'
  field field'
| name rec - field
, name rec'- field'
, name rec  field' - rec'
, name rec' field  - rec
where
field :: Functor f = Proxy name - (field - f field') -
(rec   - f rec')
 
  I don't think we need to go into lenses at all, the `field` method
  simply provides a functorial
  update function similar to `mapM`.   Of course, one could use the
 `lens`
  library to
  get more functionality but this is entirely up to the programmer.
 
  When the ORF extension is enabled, GHC should simply generate an
  instance of the class,
  in a similar way to what the lens library does


  3. I like the idea of `#x` desugaring into `field (Proxy :: Proxy x)`,
  but I don't like the concrete symbol choice:
- # is a valid operator and a bunch of libraries use it, so it won't
  be compatible with existing code.

 Ah. I didn't realise that, but assumed it was safe behind -XMagicHash.
 Yes, that's no good.

- @x might be a better choice; then you could write things like:
  view @x  rec
set  @x 3rec
over @x (+2) rec

 This could work, though it has the downside that we've been informally
 using @ for explicit type application for a long time! Does anyone know
 what the status of the proposed ExplicitTypeApplication extension is?


 I'll confess I've been keen on stealing @foo for the purpose of (Proxy ::
 Proxy foo) or (Proxy :: Proxy foo) from the type application stuff for a
 long time -- primarily because I remain rather dubious about how well the
 type application stuff can work, once you take a type and it goes through a
 usage/generalization cycle, the order of the types you can apply gets all
 jumbled up, making type application very difficult to actually use. Proxies
 on the other hand remain stable. I realize that I'm probably on the losing
 side of that debate, however. But I think it is fair to say that that
 little bit of dangling syntax will be a bone that is heavily fought over. ;)

- another nice idea (due to Eric Mertens, aka glguy), which allows us
  to avoid additional special syntax is as follows:
  - instead of using special syntax, reuse the module system
  - designate a magic module name (e.g., GHC.Records)
  - when the renamer sees a name imported from that module, it
  resolves the name by desugaring it into whatever we want
  - For example, if `GHC.Records.x` desugars into `field (Proxy ::
  Proxy x)`, we could write things like this:
 
  import GHC.Records as R
 
  view R.x  rec
  set  R.x 3rec
  over R.x (+2) rec

 Interesting; I think Edward 

Re: GHC support for the new record package

2015-01-24 Thread Daniel Trstenjak

Hi Konstantine,

 let bar' = bar{foo{val}=10}

If you're inside a record context you might just have something like:

   let bar' = bar { foo.val = 10 }

and

   let val = bar { foo.val }

or even

   let bar' = bar { foo.val %= someFunction }


This just seems to be some kind of syntactic sugar, so it's most
likely less powerful than real lenses.


Greetings,
Daniel
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs