request for reviews for my first patch -- ticket 7401

2013-08-09 Thread Ömer Sinan Ağacan
Hi all,

I just started GHC development made a commit for ticket 7401:
http://ghc.haskell.org/trac/ghc/ticket/7401

My patch is here:
https://github.com/osa1/ghc/commit/3ec257ff48372de30df59cd8854ce28954c9db95


`make test` succeeds. My test case for this patch is something like this:


data D deriving Eq

main :: IO ()
main = print ((undefined :: D) == (undefined :: D))


example:


➜  haskell  ./ghc/inplace/bin/ghc-stage2 --interactive derive.hs
GHCi, version 7.7.20130806: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( derive.hs, interpreted )
Ok, modules loaded: Main.
ghci main
True
it :: ()


This behavior(returning True) is consistent with standalone deriving version:


➜  haskell  cat derive_standalone.hs
{-# LANGUAGE StandaloneDeriving #-}

data D

deriving instance Eq D

main :: IO ()
main = print ((undefined :: D) == (undefined :: D))

➜  haskell  ./ghc/inplace/bin/ghc-stage2 --interactive derive_standalone.hs
GHCi, version 7.7.20130806: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( derive_standalone.hs, interpreted )
Ok, modules loaded: Main.
ghci main
True
it :: ()
ghci
Leaving GHCi.



However, if you want (==) implementation in this case to be `error
Void (==)`, I think I can also do that by first fixing the code
generated by StandaloneDeriving extension and then fixing my current
patch.



Any comments and reviews would be appreciated!


---
Ömer Sinan Ağacan
http://osa1.net

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


Questions about time and space profiling for non-strict langs paper and cost centre impl. of GHC

2014-05-15 Thread Ömer Sinan Ağacan
Hi all,

I'm trying to understand the paper Time and space profiling for
non-strict, higher-order functional languages[1] and I'm hoping that
experienced GHC devs here could help me clarifying some points. Here's
my question:

In Figure 5, I don't understand why no costs are attributed to `app2`
rule(substitution rule). It looks like to me that this is the function
application rule so `A` cost should be attributed here, but in the
paper `A` cost is attributed in `app1` rule, which if I understand
correctly shows how function part of an application is evaluated.

I know about the lexical scoping rule explained in 2.4 and the cost
should be attributed to the cost center in the scope of lambda
definition instead of the cost center in application site, but
Figure 5 still doesn't make sense to me.

To me it looks like that there should be two costs attributed in
application rules. First cost is evaluation of the function
part(which should be attributed in `app1` rule) and second is
substitution part, which should be attributed in `app2` rule but
according to the paper we only have the former cost, and the latter is
free(e.g. no costs are attributed in second rule).

It would be appreciated if someone could help me clarifying this. I'm
also looking for more recent papers about GHC's profiler
implementation. I'm especially interested profiling in multi-threaded
RTS.

Lastly, it'd be appreciated if someone could explain me two Bool
fields in `StgSCC` constructor of STG syntax.

Thanks!

UPDATE: I was reading the paper one more time before sending my
question and I found one more confusing part. In 4.1 it says Lexical
scoping will subsume all the costs of applying `and1` to its call
sites... but in 2.4 it says Lexical scoping: Attribute the cost to
fun, the cost centre which lexically encloses the abstraction. so
this two definitions of same thing is actually different. To me it
looks like the definition in 4.1 is wrong,, it should be definition
site, not call site. What am I missing here?

[1]: 
http://citeseerx.ist.psu.edu/viewdoc/download;jsessionid=36FE097056F4E03CCDD38B598158292E?doi=10.1.1.43.6277rep=rep1type=pdf

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Questions about time and space profiling for non-strict langs paper and cost centre impl. of GHC

2014-05-18 Thread Ömer Sinan Ağacan
Thanks Peter. Simon Marlow's talk was really interesting. After
reading the slides I read related GHC code and realized that
cost-centre stack and the stack trace printed using GHC.Stack is
same thing. `libraries/base/GHC/Stack.hsc` has this definition:

currentCallStack :: IO [String]
currentCallStack = ccsToStrings = getCurrentCCS ()

So actually string representation of cost-centre stack is returned
when current call stack is requested.

(off-topic: I'm wondering why an empty tuple is passed to `getCurrentCSS`?)

Now my first question is: Assuming stack traces are implemented as
explained by Simon Marlow in his talk and slides, can we say that
costs are always assigned to top cost-centre in the stack? So in case
of an allocation or when tick counter triggered, can I say that
always the top-most cost-centre in `rCCCs` register will be modified?
(then `inherited` costs would be calculated)

I'm asking this because I can't read the code generated for
cost-centre annotations(code generated for StgSCC code) because for
that I need to follow code generation through compilation to Cmm, but
I don't know anything about Cmm yet.

As far as I can understand, current implementation is different from
what's explained in Sansom and Jones, for example

* I can't see SUB cost-centre in list of built-in cost-centres in
`rts/Profiling.c`.
* We now have stacks which are assigned to RHS of bindings.

I tried reading output of -ddump-stg but generated STG is confusing.
For example, this function:

fib :: Integer - Integer
fib 0 = 1
fib 1 = 1
fib n = fib (n - 1) + fib (n - 2)

is annotated with `CCS_DONT_CARE`. Why is that? Also, I can see
`_push_` and `_tick_`(what's this?) instructions placed in generated
STG but no `_call_` instructions. There is also something like `CCCS`
in generated STG but I have no ideas about this.

So in short I'm trying to understand how cost-centre related
annotations are generated and how are they used. Any paper/source
code/blog post suggestions would be very appreciated. As far as I can
see current implementation is different than ones explained in
slides/papers.

Thanks,

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: Questions about time and space profiling for non-strict langs paper and cost centre impl. of GHC

2014-05-18 Thread Ömer Sinan Ağacan
Thanks again for the answer.

 Not sure what _call_ is suppose to be. What's the context?

In Simon Marlow's slides, stack traces are implemented in terms of
call and push operations. I guess `push` in STG syntax is stands
for push operation explained in the slides but as far as I can see
call is missing in generated STG.

 There is also something like `CCCS` in generated STG but I have no
 ideas about this.

 That's simply current cost-centre stack. I like to think that the hint
 of silliness was intentional.

Yes, but I'm wondering what does that syntax in STG mean
operationally? For example, here's some part of generated STG:

let {
  sat_s2OT [Occ=Once] :: GHC.Integer.Type.Integer
  [LclId, Str=DmdType] =
  CCCS GHC.Integer.Type.S#! [0];
}

What does CCCS stand for here? I guess in long term it'd be best for
me to learn Cmm and see the generated code for this syntax to
understand what does it really do.(assuming Cmm has better
documentation that STG :) )

 Sure. Better place for quick queries might be #ghc on FreeNode though -
 my nick is petermw.

Great, my nick is osa1 and I'll be pinging you for short questions.
Thanks again!

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


segfault in RTS - can anyone help me tracking this bug down?

2014-05-28 Thread Ömer Sinan Ağacan
Hi all,

I'm suffering from a RTS bug(probably GC related) that makes making
progress in my GSoC project impossible. I have very limited knowledge
of GHC internals and I currently have no idea how to produce a minimal
program that demonstrates the bug. I wrote how to reproduce it and gdb
backtrace when segfault happens in a short blog post:
http://osa1.net/posts/2014-05-27-worst-bug.html . As also written in
the blog post, changing generation count of generational GC will makes
the bug disappear in some cases, but it's not a solution.

I also pasted backtrace output below for those who don't want to click links.

GHC version used is 7.8.2.

If anyone give me some pointers to understand what's going wrong or
how can I produce a simple program that demonstrates the bug, I'd like
to work on that. I'm basically stuck and I can't make any progress
with this bug.

Thanks,
Ömer

[  5 of 202] Compiling GHC.Unicode[boot] ( GHC/Unicode.hs-boot,
dist/build/GHC/Unicode.js_p_o-boot )
Detaching after fork from child process 3382.
[  6 of 202] Compiling GHC.IO[boot] ( GHC/IO.hs-boot,
dist/build/GHC/IO.js_p_o-boot )
Detaching after fork from child process 3383.
[  7 of 202] Compiling GHC.Exception[boot] ( GHC/Exception.lhs-boot,
dist/build/GHC/Exception.js_p_o-boot )
Detaching after fork from child process 3384.
[ 51 of 202] Compiling GHC.Fingerprint[boot] (
GHC/Fingerprint.hs-boot, dist/build/GHC/Fingerprint.js_p_o-boot )
Detaching after fork from child process 3385.
[ 55 of 202] Compiling GHC.IO.Exception[boot] (
GHC/IO/Exception.hs-boot, dist/build/GHC/IO/Exception.js_p_o-boot )
Detaching after fork from child process 3386.
[ 75 of 202] Compiling Foreign.C.Types  ( Foreign/C/Types.hs,
dist/build/Foreign/C/Types.js_p_o )

Program received signal SIGSEGV, Segmentation fault.
0x0425d5c4 in LOOKS_LIKE_CLOSURE_PTR (p=0x0) at
includes/rts/storage/ClosureMacros.h:258
258 includes/rts/storage/ClosureMacros.h: No such file or directory.
(gdb) bt
#0  0x0425d5c4 in LOOKS_LIKE_CLOSURE_PTR (p=0x0) at
includes/rts/storage/ClosureMacros.h:258
#1  0x0425f776 in scavenge_mutable_list1 (bd=0x7fffe5c02a00,
gen=0x4d1fd48) at rts/sm/Scav.c:1400
#2  0x0425fa13 in scavenge_capability_mut_Lists1
(cap=0x4cfe5c0 MainCapability) at rts/sm/Scav.c:1493
#3  0x04256b66 in GarbageCollect (collect_gen=0,
do_heap_census=rtsFalse, gc_type=2,
cap=0x4cfe5c0 MainCapability) at rts/sm/GC.c:342
#4  0x042454a3 in scheduleDoGC (pcap=0x7fffc198,
task=0x4d32b60, force_major=rtsFalse)
at rts/Schedule.c:1650
#5  0x04243de4 in schedule (initialCapability=0x4cfe5c0
MainCapability, task=0x4d32b60)
at rts/Schedule.c:553
#6  0x04246436 in scheduleWaitThread (tso=0x76708d60,
ret=0x0, pcap=0x7fffc2c0) at rts/Schedule.c:2346
#7  0x0423e9b4 in rts_evalLazyIO (cap=0x7fffc2c0,
p=0x477f850, ret=0x0) at rts/RtsAPI.c:500
#8  0x04241666 in real_main () at rts/RtsMain.c:63
#9  0x04241759 in hs_main (argc=237, argv=0x7fffc448,
main_closure=0x477f850, rts_config=...)
at rts/RtsMain.c:114
#10 0x00408ea7 in main ()
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: segfault in RTS - can anyone help me tracking this bug down?

2014-05-30 Thread Ömer Sinan Ağacan
Hi all,

Here's an update. While playing with some parameters I managed to
produce a case where compilation still fails, but this time with an
assertion error instead of a segfault:

... snipped ...
[112 of 202] Compiling System.Posix.Types ( System/Posix/Types.hs,
dist/build/System/Posix/Types.js_p_o )
ghcjs: internal error: ASSERTION FAILED: file rts/sm/Scav.c, line 1400

(GHC version 7.8.2 for x86_64_unknown_linux)
Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

Program received signal SIGABRT, Aborted.
0x7687f849 in raise () from /lib64/libc.so.6
(gdb) bt
#0  0x7687f849 in raise () from /lib64/libc.so.6
#1  0x76880cd8 in abort () from /lib64/libc.so.6
#2  0x04238a27 in rtsFatalInternalErrorFn (s=0x4554e60
ASSERTION FAILED: file %s, line %u\n,
ap=0x7fffbe58) at rts/RtsMessages.c:170
#3  0x0423865f in barf (s=0x4554e60 ASSERTION FAILED: file
%s, line %u\n) at rts/RtsMessages.c:42
#4  0x042386c2 in _assertFail (filename=0x4559fbd
rts/sm/Scav.c, linenum=1400) at rts/RtsMessages.c:57
#5  0x042565e9 in scavenge_mutable_list1 (bd=0x7fffe7402dc0,
gen=0x4d15d88) at rts/sm/Scav.c:1400
#6  0x04256873 in scavenge_capability_mut_Lists1
(cap=0x4cf49c0 MainCapability) at rts/sm/Scav.c:1493
#7  0x0424d9c6 in GarbageCollect (collect_gen=0,
do_heap_census=rtsFalse, gc_type=2,
cap=0x4cf49c0 MainCapability) at rts/sm/GC.c:342
#8  0x0423c303 in scheduleDoGC (pcap=0x7fffc188,
task=0x4d28ba0, force_major=rtsFalse)
at rts/Schedule.c:1650
#9  0x0423ac44 in schedule (initialCapability=0x4cf49c0
MainCapability, task=0x4d28ba0)
at rts/Schedule.c:553
#10 0x0423d296 in scheduleWaitThread (tso=0x76708d60,
ret=0x0, pcap=0x7fffc2b0) at rts/Schedule.c:2346
#11 0x04235814 in rts_evalLazyIO (cap=0x7fffc2b0,
p=0x4776850, ret=0x0) at rts/RtsAPI.c:500
#12 0x042384c6 in real_main () at rts/RtsMain.c:63
#13 0x042385b9 in hs_main (argc=238, argv=0x7fffc438,
main_closure=0x4776850, rts_config=...)
at rts/RtsMain.c:114
#14 0x00408ea7 in main ()

I'm not sure if that helps but I just wanted to share in case it
helps. I'm currently trying to come up with a single file that causes
this problem.

---
Ömer Sinan Ağacan
http://osa1.net


2014-05-29 18:50 GMT+03:00 Luite Stegeman stege...@gmail.com:



 On Thu, May 29, 2014 at 5:41 PM, Simon Marlow marlo...@gmail.com wrote:

 Yeah, vagrant would be fine.

 Do you have any FFI or other strange things in GHCJS that might
 conceivably cause this?


 Not in GHCJS itself as far as I know, but its dependency list is rather
 long, unfortunately.

 luite

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


can a StgRhs have NoCCS when -prof is provided?

2014-06-05 Thread Ömer Sinan Ağacan
Hi all,

Can a StgRhs have `NoCCS` as cost-centre stack when -prof is provided
while compiling? Or is it always oneOf [CurrentCCS, DontCareCCS,
SingletonCCS]?

I presume that since we have CCS constructor DontCareCCS and CCS
field of StgRhs constructors are not `Maybe CostCentreStack` (so
they're not optional), when -prof is provided CCS fields should not be
filled with NoCCS(if we still don't care about CCS for some reason, it
should be DontCareCCS) but I just wanted to make sure.

Thanks.

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: RFC: Phabricator for patches and code review

2014-06-06 Thread Ömer Sinan Ağacan
2014-06-06 7:05 GMT+03:00 Austin Seipp aus...@well-typed.com:
  2) Phabricator in particular makes it very easy to submit patches for
 review. To submit a patch, I just run the command 'arc diff' and it
 Does The Right Thing. It also makes it easy to ensure people are
 *alerted* when a patch might be relevant to them.

This sounds really good. I was thinking about sending an email about
this for a while now. I'm reading some parts of GHC and there are lots
of small patches I'd like to submit for reviews. Most of the time
these are 10 lines of changes. But trac makes everything so hard and
the interface is so horrible, I'm ending up not sending the patch.
Also, testing is a huge problem for me. I can't test GHC on my
laptop(which is my only development environment) because it takes
forever to finish.

With something like Github and a CI server(Jenkins/Travis/whatever)
integrated to the Github repository that runs tests on pull request,
it would be super easy for new contributors to submit small patches.

As far as I can understand(altough currently I can't see how to send a
patch) Phabricator helps sending pull requests/patches, but does it
help with testing too?

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Interesting whoCreated output (stack trace related)

2014-06-25 Thread Ömer Sinan Ağacan
Hi all,

I'm running this program:

  {-# LANGUAGE DeriveDataTypeable, ScopedTypeVariables #-}
  import GHC.Stack
  import Control.Exception.Base
  import Data.Typeable

  data MyException = MyException deriving (Show, Typeable)

  instance Exception MyException

  err1 :: IO Integer
  err1 = {-# SCC error1 #-} err2 = return

  err2 :: IO Integer
  err2 = {-# SCC error2 #-} throw MyException

  main = print = whoCreated = catch err1 = (\(_ :: MyException)
- return (42 :: Integer))

I'd expect `whoCreated` to return something like [Main.CAF, Main.main,
Main.main.\] but instead this is the output:

  [Main.CAF (entire-module),Main.err2
(ioerr.hs:14:1-43),Main.error2 (ioerr.hs:14:27-43),Main.main
(ioerr.hs:16:1-103),Main.main.\\ (ioerr.hs:16:81-102)]

This output has two things that look somewhat weird to me. First, I'd
expect cost-centre stack to be restored when exception is catched and
then program would produce shorter stack trace like I mentioned
above.(without err1 or err2 calls)

Second, when no cost-centre restoring is done, I'd expect stack trace
to include `Main.err1` and `Main.error1`.

So can anyone explain my why stack trace contains err2 calls but not
err1 calls? I think none of error1 and error2 should have been
included in the stack trace or both of them should have been included.

Thanks.

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Why we need CCS entries in apply functions (rts/Apply.cmm and rts/StgStdThunks.cmm)

2014-07-01 Thread Ömer Sinan Ağacan
Hi all,

Code for entering cost-centres before executing the function/thunk
body is generated in `compiler/codeGen/StgCmmBind.hs`, by `thunkCode`
and `closureCodeBody` functions. But we also have some
`enterCostCentreThunk` and `enterCostCentreFun` calls in
`rts/Apply.cmm` and `rts/StgStdThunks.cmm`. I'm wondering why are
those necessary. Thunk/function bodies already have CCS entries
generated by functions in StgCmmBind so I'm having trouble seeing the
need for this additional entries.

Can anyone explain those to me?

Thanks,

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


biographical profiling is broken?

2014-08-07 Thread Ömer Sinan Ağacan
Hi all,

I'm trying to use LDV profiling features of GHC but I'm failing.
Here's what I try:

(I'm using GHC 7.8.2)

* I'm compiling my app with `-prof` and I'm also using `-fprof-auto`
just to be sure.
* I'm running my app using `+RTS -hbdrag,void` as described in the
docs. 
(https://www.haskell.org/ghc/docs/latest/html/users_guide/prof-heap.html#biography-prof)

This always generates an empty MyApp.hp file. There's only this header
in the generated file:

  JOB MyApp +RTS -hd -hbdrag,void,lag
  DATE Thu Aug  7 18:14 2014
  SAMPLE_UNIT seconds
  VALUE_UNIT bytes
  BEGIN_SAMPLE 0.00
  END_SAMPLE 0.00
  BEGIN_SAMPLE 0.10
  END_SAMPLE 0.10

I tried different programs, from hello world to a complex language
interpreter. I always get the same file with only a header.

* I also tried adding more arguments like `-hc`, `-hm`, `-hr` etc. but
I got same results.

I feel like the feature is broken. I checked the test suite to find
some working LDV profiling programs. But as far as I can see we don't
have any tests for LDV stuff. There's a `bio001.stdout` which I
believe is related with biographical profiling(which means LDV) but
again AFAICS it's not used.

(I'm not having any different behaviors or exceptions while running
programs using LDV RTS arguments.)

Can anyone help me with this? Is anyone using this feature? Am I right
that this feature is not tested?

Thanks.

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: How's the integration of DWARF support coming along?

2014-08-13 Thread Ömer Sinan Ağacan
Is this stack trace support different than what we have currently?
(e.g. the one implemented with GHC.Stack and cost centers)

---
Ömer Sinan Ağacan
http://osa1.net


2014-08-13 18:02 GMT+03:00 Johan Tibell johan.tib...@gmail.com:
 Hi,

 How's the integration of DWARF support coming along? It's probably one of
 the most important improvements to the runtime in quite some time since
 unlocks *two* important features, namely

  * trustworthy profiling (using e.g. Linux perf events and other
 low-overhead, code preserving, sampling profilers), and
  * stack traces.

 The former is really important to move our core libraries performance up a
 notch. Right now -prof is too invasive for it to be useful when evaluating
 the hotspots in these libraries (which are already often heavily tuned).

 The latter one is really important for real life Haskell on the server,
 where you can sometimes can get some crash that only happens once a day
 under very specific conditions. Knowing where the crash happens is then
 *very* useful.

 -- Johan


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

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


Re: How's the integration of DWARF support coming along?

2014-08-13 Thread Ömer Sinan Ağacan
Will generated stack traces be different that

---
Ömer Sinan Ağacan
http://osa1.net


2014-08-13 19:56 GMT+03:00 Johan Tibell johan.tib...@gmail.com:
 Yes, it doesn't use any code modification so it doesn't have runtime
 overhead (except when generating the actual trace) or interfere with
 compiler optimizations. In other words you can actually have it enabled at
 all time. It only requires that you compile with -g, just like with a C
 compiler.


 On Wed, Aug 13, 2014 at 6:45 PM, Ömer Sinan Ağacan omeraga...@gmail.com
 wrote:

 Is this stack trace support different than what we have currently?
 (e.g. the one implemented with GHC.Stack and cost centers)

 ---
 Ömer Sinan Ağacan
 http://osa1.net


 2014-08-13 18:02 GMT+03:00 Johan Tibell johan.tib...@gmail.com:
  Hi,
 
  How's the integration of DWARF support coming along? It's probably one
  of
  the most important improvements to the runtime in quite some time since
  unlocks *two* important features, namely
 
   * trustworthy profiling (using e.g. Linux perf events and other
  low-overhead, code preserving, sampling profilers), and
   * stack traces.
 
  The former is really important to move our core libraries performance up
  a
  notch. Right now -prof is too invasive for it to be useful when
  evaluating
  the hotspots in these libraries (which are already often heavily tuned).
 
  The latter one is really important for real life Haskell on the server,
  where you can sometimes can get some crash that only happens once a day
  under very specific conditions. Knowing where the crash happens is then
  *very* useful.
 
  -- Johan
 
 
  ___
  ghc-devs mailing list
  ghc-devs@haskell.org
  http://www.haskell.org/mailman/listinfo/ghc-devs
 


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


Re: How's the integration of DWARF support coming along?

2014-08-13 Thread Ömer Sinan Ağacan
Sorry for my previous email. (used a gmail shortcut by mistake)

We won't have stacks as we have in imperative(without TCO) and strict
languages. So we still need some kind of emulation and I think this
means some extra run-time operations. I'm wondering about two things:

1) Do we still get same traces as we get using GHC.Stack right now?
2) If yes, then how can we have that without any runtime costs?

Thanks and sorry again for my previous email.

---
Ömer Sinan Ağacan
http://osa1.net


2014-08-13 20:08 GMT+03:00 Ömer Sinan Ağacan omeraga...@gmail.com:
 Will generated stack traces be different that

 ---
 Ömer Sinan Ağacan
 http://osa1.net


 2014-08-13 19:56 GMT+03:00 Johan Tibell johan.tib...@gmail.com:
 Yes, it doesn't use any code modification so it doesn't have runtime
 overhead (except when generating the actual trace) or interfere with
 compiler optimizations. In other words you can actually have it enabled at
 all time. It only requires that you compile with -g, just like with a C
 compiler.


 On Wed, Aug 13, 2014 at 6:45 PM, Ömer Sinan Ağacan omeraga...@gmail.com
 wrote:

 Is this stack trace support different than what we have currently?
 (e.g. the one implemented with GHC.Stack and cost centers)

 ---
 Ömer Sinan Ağacan
 http://osa1.net


 2014-08-13 18:02 GMT+03:00 Johan Tibell johan.tib...@gmail.com:
  Hi,
 
  How's the integration of DWARF support coming along? It's probably one
  of
  the most important improvements to the runtime in quite some time since
  unlocks *two* important features, namely
 
   * trustworthy profiling (using e.g. Linux perf events and other
  low-overhead, code preserving, sampling profilers), and
   * stack traces.
 
  The former is really important to move our core libraries performance up
  a
  notch. Right now -prof is too invasive for it to be useful when
  evaluating
  the hotspots in these libraries (which are already often heavily tuned).
 
  The latter one is really important for real life Haskell on the server,
  where you can sometimes can get some crash that only happens once a day
  under very specific conditions. Knowing where the crash happens is then
  *very* useful.
 
  -- Johan
 
 
  ___
  ghc-devs mailing list
  ghc-devs@haskell.org
  http://www.haskell.org/mailman/listinfo/ghc-devs
 


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


cabal directory structure under /libraries/ for a lib that uses Rts.h

2014-09-30 Thread Ömer Sinan Ağacan
Hi all,

I'm trying to implement https://ghc.haskell.org/trac/ghc/ticket/5364 ,
I did the coding part but I'm having trouble compiling it/adding it as
a part of GHC libraries.

My library is just one hsc file with a line `#include Rts.h` in it.
Any ideas what should I do to make it compiled with GHC?

Thanks..

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: cabal directory structure under /libraries/ for a lib that uses Rts.h

2014-10-02 Thread Ömer Sinan Ağacan
 Well, which library should it be part of? Add it to the exposed-modules
 list there and it should get compiled.

It's not only a get it compiled problem, even if I add it to base or
some other lib and get it compiled, it's failing with a undefined
reference linker error. I'm trying to use a function from
`rts/RtsFlags.c`. I can define the function elsewhere but I still link
it with `RtsFlags.c` because I'm using `RtsFlags` from that file.

Any ideas?

---
Ömer Sinan Ağacan
http://osa1.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://www.haskell.org/mailman/listinfo/ghc-devs


Re: FYI: Cabal-1.22.1.0 has been released

2015-02-22 Thread Ömer Sinan Ağacan
Where can we see the changelog?
https://github.com/haskell/cabal/blob/master/Cabal/changelog - this
file has not been updated.

2015-02-22 12:08 GMT-05:00 Herbert Valerio Riedel hvrie...@gmail.com:
 On 2015-02-22 at 13:35:33 +0100, Johan Tibell wrote:
 We will probably want to ship that with GHC 7.10.

 I've updated the ghc-7.10 branch's Cabal submodule to point to commit
 9225192b7afc2b96062fb991cc3d16cccb9de1b0 (which corresponds to the
 Cabal-v1.22.1.0 tag)

 Cheers,
   hvr
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: expanding type synonyms in error messages

2015-06-18 Thread Ömer Sinan Ağacan
It's good to see that I'm not the only one who wants this. I'm doing
some GHC hacking nowadays and I'll give it a try.

2015-06-18 4:41 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
 I wanted to add that synonym expansion would be especially helpful in
 error-messages like:

 Expected type: non-expanded, small type, like Producer a m ()
 Actual type: your type, like Proxy a a' b b' m v

 I would be glad if we could have an expansions enabling flag in GHC, and
 could consider turning it on by default if it will look good for that.

 16 черв. 2015 22:44 Richard Eisenberg e...@cis.upenn.edu пише:

 GHC tries hard to preserve type synonyms where possible, but of course, it
 can't preserve all of them. The general rule it tries to follow is: preserve
 vanilla type synonyms; expand type families. This is true both in expected
 types and actual types.
 If you have a case where you believe that GHC could preserve a type
 synonym in an expected type, submit a bug report. (Note that constraint
 synonyms are particularly hard to preserve!)

 It would be very easy to report both the synonym-preserving form and the
 expanded form in an error report, at the cost of making error reports even
 more verbose. You're welcome to submit a feature request, and this would
 likely make a good first patch to GHC if you want to get your hands dirty.
 I'd personally prefer the feature to be protected behind a flag (to avoid
 seeing that `String` expands to `[Char]` everywhere, for example), but
 others may feel differently here.

 Richard

 On Jun 16, 2015, at 11:20 AM, Ömer Sinan Ağacan omeraga...@gmail.com
 wrote:

  Hi all,
 
  While working with complex types with lots of arguments etc. errors are
  becoming annoying very fast. For example, GHC prints errors in this way:
 
 Expected type: type without any synonyms
   Actual type: type with synonyms
 
  Now I have to expand that synonym in my head to understand the error.
 
  I was wondering if implementing something like this is possible:
 
  In type error messages, GHC also prints types that are cleaned from type
  synonyms. Maybe something like this:
 
  Expected type: type1
 (without synonyms): type1, synonyms are expanded
Actual type: type2
 (without synonyms): type2, synonyms are expanded
 
  If this is not always desirable for some reason, we can hide this
  behavior
  behind a flag.
 
  What do GHC devs think about this? Is this, in theory, possible to do?
  How hard
  would it be to implement this?
 
  Thanks.
  ___
  ghc-devs mailing list
  ghc-devs@haskell.org
  http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: expanding type synonyms in error messages

2015-06-19 Thread Ömer Sinan Ağacan
Done: https://ghc.haskell.org/trac/ghc/ticket/10547

2015-06-19 9:12 GMT-04:00 Richard Eisenberg e...@cis.upenn.edu:
 Don't forget to make a Feature Request on Trac 
 (https://ghc.haskell.org/trac/ghc/newticket) with a link to the wiki page. 
 Trac is really the only way things like this don't get lost.

 Thanks!

 Richard


 On Jun 19, 2015, at 9:07 AM, Ömer Sinan Ağacan omeraga...@gmail.com wrote:

 Great, thanks Kostiantyn! I'm looking for simple examples that we can
 add to GHC testsuite, if I find something I'll update the wiki page
 also.

 I made some progress on the patch, I think I can hopefully submit
 something this weekend for reviews.

 2015-06-19 5:16 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
 Created some initial wiki-page with just one example, will keep it in mind
 to add more as seen.

 https://wiki.haskell.org/Expanding_type_synonyms_in_error_messages_proposal

 On Fri, Jun 19, 2015 at 10:42 AM, Simon Peyton Jones simo...@microsoft.com
 wrote:

 On this thread, a representative collection of *reproducible examples*
 with the actual error message and the desired one, would be tremendously
 helpful.  Lacking that, it’s hard to know where to begin.   (Creating the
 examples takes a bit of work, I know.)



 Start a wiki page!  Stuff in email threads gets lost



 Simon



 From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of
 Christopher Allen
 Sent: 19 June 2015 04:27
 To: Ömer Sinan Ağacan
 Cc: ghc-devs
 Subject: Re: expanding type synonyms in error messages



 Just to add my own +1, having this when working with streaming libraries
 (I've needed it less with lens, oddly) would be a tremendous help for 
 people
 learning them I think. I think I've run into the same thing as Kostiantyn 
 in
 the past.



 On Thu, Jun 18, 2015 at 9:42 PM, Ömer Sinan Ağacan omeraga...@gmail.com
 wrote:

 It's good to see that I'm not the only one who wants this. I'm doing
 some GHC hacking nowadays and I'll give it a try.


 2015-06-18 4:41 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
 I wanted to add that synonym expansion would be especially helpful in
 error-messages like:

 Expected type: non-expanded, small type, like Producer a m ()
 Actual type: your type, like Proxy a a' b b' m v

 I would be glad if we could have an expansions enabling flag in GHC, and
 could consider turning it on by default if it will look good for that.

 16 черв. 2015 22:44 Richard Eisenberg e...@cis.upenn.edu пише:

 GHC tries hard to preserve type synonyms where possible, but of course,
 it
 can't preserve all of them. The general rule it tries to follow is:
 preserve
 vanilla type synonyms; expand type families. This is true both in
 expected
 types and actual types.
 If you have a case where you believe that GHC could preserve a type
 synonym in an expected type, submit a bug report. (Note that constraint
 synonyms are particularly hard to preserve!)

 It would be very easy to report both the synonym-preserving form and
 the
 expanded form in an error report, at the cost of making error reports
 even
 more verbose. You're welcome to submit a feature request, and this
 would
 likely make a good first patch to GHC if you want to get your hands
 dirty.
 I'd personally prefer the feature to be protected behind a flag (to
 avoid
 seeing that `String` expands to `[Char]` everywhere, for example), but
 others may feel differently here.

 Richard

 On Jun 16, 2015, at 11:20 AM, Ömer Sinan Ağacan omeraga...@gmail.com
 wrote:

 Hi all,

 While working with complex types with lots of arguments etc. errors
 are
 becoming annoying very fast. For example, GHC prints errors in this
 way:

   Expected type: type without any synonyms
 Actual type: type with synonyms

 Now I have to expand that synonym in my head to understand the error.

 I was wondering if implementing something like this is possible:

 In type error messages, GHC also prints types that are cleaned from
 type
 synonyms. Maybe something like this:

Expected type: type1
   (without synonyms): type1, synonyms are expanded
  Actual type: type2
   (without synonyms): type2, synonyms are expanded

 If this is not always desirable for some reason, we can hide this
 behavior
 behind a flag.

 What do GHC devs think about this? Is this, in theory, possible to
 do?
 How hard
 would it be to implement this?

 Thanks.
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs





 --

 Chris Allen

 Currently working on http://haskellbook.com


 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http

Re: expanding type synonyms in error messages

2015-06-19 Thread Ömer Sinan Ağacan
Great, thanks Kostiantyn! I'm looking for simple examples that we can
add to GHC testsuite, if I find something I'll update the wiki page
also.

I made some progress on the patch, I think I can hopefully submit
something this weekend for reviews.

2015-06-19 5:16 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
 Created some initial wiki-page with just one example, will keep it in mind
 to add more as seen.

 https://wiki.haskell.org/Expanding_type_synonyms_in_error_messages_proposal

 On Fri, Jun 19, 2015 at 10:42 AM, Simon Peyton Jones simo...@microsoft.com
 wrote:

 On this thread, a representative collection of *reproducible examples*
 with the actual error message and the desired one, would be tremendously
 helpful.  Lacking that, it’s hard to know where to begin.   (Creating the
 examples takes a bit of work, I know.)



 Start a wiki page!  Stuff in email threads gets lost



 Simon



 From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of
 Christopher Allen
 Sent: 19 June 2015 04:27
 To: Ömer Sinan Ağacan
 Cc: ghc-devs
 Subject: Re: expanding type synonyms in error messages



 Just to add my own +1, having this when working with streaming libraries
 (I've needed it less with lens, oddly) would be a tremendous help for people
 learning them I think. I think I've run into the same thing as Kostiantyn in
 the past.



 On Thu, Jun 18, 2015 at 9:42 PM, Ömer Sinan Ağacan omeraga...@gmail.com
 wrote:

 It's good to see that I'm not the only one who wants this. I'm doing
 some GHC hacking nowadays and I'll give it a try.


 2015-06-18 4:41 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
  I wanted to add that synonym expansion would be especially helpful in
  error-messages like:
 
  Expected type: non-expanded, small type, like Producer a m ()
  Actual type: your type, like Proxy a a' b b' m v
 
  I would be glad if we could have an expansions enabling flag in GHC, and
  could consider turning it on by default if it will look good for that.
 
  16 черв. 2015 22:44 Richard Eisenberg e...@cis.upenn.edu пише:
 
  GHC tries hard to preserve type synonyms where possible, but of course,
  it
  can't preserve all of them. The general rule it tries to follow is:
  preserve
  vanilla type synonyms; expand type families. This is true both in
  expected
  types and actual types.
  If you have a case where you believe that GHC could preserve a type
  synonym in an expected type, submit a bug report. (Note that constraint
  synonyms are particularly hard to preserve!)
 
  It would be very easy to report both the synonym-preserving form and
  the
  expanded form in an error report, at the cost of making error reports
  even
  more verbose. You're welcome to submit a feature request, and this
  would
  likely make a good first patch to GHC if you want to get your hands
  dirty.
  I'd personally prefer the feature to be protected behind a flag (to
  avoid
  seeing that `String` expands to `[Char]` everywhere, for example), but
  others may feel differently here.
 
  Richard
 
  On Jun 16, 2015, at 11:20 AM, Ömer Sinan Ağacan omeraga...@gmail.com
  wrote:
 
   Hi all,
  
   While working with complex types with lots of arguments etc. errors
   are
   becoming annoying very fast. For example, GHC prints errors in this
   way:
  
  Expected type: type without any synonyms
Actual type: type with synonyms
  
   Now I have to expand that synonym in my head to understand the error.
  
   I was wondering if implementing something like this is possible:
  
   In type error messages, GHC also prints types that are cleaned from
   type
   synonyms. Maybe something like this:
  
   Expected type: type1
  (without synonyms): type1, synonyms are expanded
 Actual type: type2
  (without synonyms): type2, synonyms are expanded
  
   If this is not always desirable for some reason, we can hide this
   behavior
   behind a flag.
  
   What do GHC devs think about this? Is this, in theory, possible to
   do?
   How hard
   would it be to implement this?
  
   Thanks.
   ___
   ghc-devs mailing list
   ghc-devs@haskell.org
   http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
 
  ___
  ghc-devs mailing list
  ghc-devs@haskell.org
  http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs





 --

 Chris Allen

 Currently working on http://haskellbook.com


 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: expanding type synonyms in error messages

2015-06-26 Thread Ömer Sinan Ağacan
Update: I have a patch, it's not quite ready for reviews, but I'm now
getting this error message:

Main.hs:17:26: error:
Couldn't match type ‘[Char]’ with ‘()’
Expected type: Proxy () String () X IO ()
 (aka. Proxy () [Char] () X IO ())
  Actual type: Consumer String IO String
 (aka. Proxy () [Char] () X IO [Char])
In the second argument of ‘(-)’, namely ‘doubleUp’
In the second argument of ‘($)’, namely ‘loop - doubleUp’
cabal: Error: some packages failed to install:
ghc-ty-patch-0.1.0.0 failed during the building phase. The exception was:
ExitFailure 1

I'll tidy the code a bit, add a command line flag etc. and submit for reviews.

2015-06-19 10:13 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
 Great, thanks for doing this! I'm afraid even if you succeed with patch we
 would still need more real-world examples that show the need for this
 feature, and I think this is separate from GHC tests, as they don't need to
 be realistic, but of course please continue and hopefully more examples will
 come.

 19 черв. 2015 16:19 Ömer Sinan Ağacan omeraga...@gmail.com пише:

 Done: https://ghc.haskell.org/trac/ghc/ticket/10547

 2015-06-19 9:12 GMT-04:00 Richard Eisenberg e...@cis.upenn.edu:
  Don't forget to make a Feature Request on Trac
  (https://ghc.haskell.org/trac/ghc/newticket) with a link to the wiki page.
  Trac is really the only way things like this don't get lost.
 
  Thanks!
 
  Richard
 
 
  On Jun 19, 2015, at 9:07 AM, Ömer Sinan Ağacan omeraga...@gmail.com
  wrote:
 
  Great, thanks Kostiantyn! I'm looking for simple examples that we can
  add to GHC testsuite, if I find something I'll update the wiki page
  also.
 
  I made some progress on the patch, I think I can hopefully submit
  something this weekend for reviews.
 
  2015-06-19 5:16 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
  Created some initial wiki-page with just one example, will keep it in
  mind
  to add more as seen.
 
 
  https://wiki.haskell.org/Expanding_type_synonyms_in_error_messages_proposal
 
  On Fri, Jun 19, 2015 at 10:42 AM, Simon Peyton Jones
  simo...@microsoft.com
  wrote:
 
  On this thread, a representative collection of *reproducible
  examples*
  with the actual error message and the desired one, would be
  tremendously
  helpful.  Lacking that, it’s hard to know where to begin.   (Creating
  the
  examples takes a bit of work, I know.)
 
 
 
  Start a wiki page!  Stuff in email threads gets lost
 
 
 
  Simon
 
 
 
  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of
  Christopher Allen
  Sent: 19 June 2015 04:27
  To: Ömer Sinan Ağacan
  Cc: ghc-devs
  Subject: Re: expanding type synonyms in error messages
 
 
 
  Just to add my own +1, having this when working with streaming
  libraries
  (I've needed it less with lens, oddly) would be a tremendous help for
  people
  learning them I think. I think I've run into the same thing as
  Kostiantyn in
  the past.
 
 
 
  On Thu, Jun 18, 2015 at 9:42 PM, Ömer Sinan Ağacan
  omeraga...@gmail.com
  wrote:
 
  It's good to see that I'm not the only one who wants this. I'm doing
  some GHC hacking nowadays and I'll give it a try.
 
 
  2015-06-18 4:41 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
  I wanted to add that synonym expansion would be especially helpful
  in
  error-messages like:
 
  Expected type: non-expanded, small type, like Producer a m ()
  Actual type: your type, like Proxy a a' b b' m v
 
  I would be glad if we could have an expansions enabling flag in GHC,
  and
  could consider turning it on by default if it will look good for
  that.
 
  16 черв. 2015 22:44 Richard Eisenberg e...@cis.upenn.edu пише:
 
  GHC tries hard to preserve type synonyms where possible, but of
  course,
  it
  can't preserve all of them. The general rule it tries to follow is:
  preserve
  vanilla type synonyms; expand type families. This is true both in
  expected
  types and actual types.
  If you have a case where you believe that GHC could preserve a type
  synonym in an expected type, submit a bug report. (Note that
  constraint
  synonyms are particularly hard to preserve!)
 
  It would be very easy to report both the synonym-preserving form
  and
  the
  expanded form in an error report, at the cost of making error
  reports
  even
  more verbose. You're welcome to submit a feature request, and this
  would
  likely make a good first patch to GHC if you want to get your hands
  dirty.
  I'd personally prefer the feature to be protected behind a flag (to
  avoid
  seeing that `String` expands to `[Char]` everywhere, for example),
  but
  others may feel differently here.
 
  Richard
 
  On Jun 16, 2015, at 11:20 AM, Ömer Sinan Ağacan
  omeraga...@gmail.com
  wrote:
 
  Hi all,
 
  While working with complex types with lots of arguments etc.
  errors
  are
  becoming annoying very fast. For example, GHC prints errors in
  this
  way:
 
Expected type: type without any synonyms
  Actual type: type

Re: expanding type synonyms in error messages

2015-06-26 Thread Ömer Sinan Ağacan
Created a patch for reviews/feedbacks: https://phabricator.haskell.org/D1016

2015-06-26 12:40 GMT-04:00 Ömer Sinan Ağacan omeraga...@gmail.com:
 Update: I have a patch, it's not quite ready for reviews, but I'm now
 getting this error message:

 Main.hs:17:26: error:
 Couldn't match type ‘[Char]’ with ‘()’
 Expected type: Proxy () String () X IO ()
  (aka. Proxy () [Char] () X IO ())
   Actual type: Consumer String IO String
  (aka. Proxy () [Char] () X IO [Char])
 In the second argument of ‘(-)’, namely ‘doubleUp’
 In the second argument of ‘($)’, namely ‘loop - doubleUp’
 cabal: Error: some packages failed to install:
 ghc-ty-patch-0.1.0.0 failed during the building phase. The exception was:
 ExitFailure 1

 I'll tidy the code a bit, add a command line flag etc. and submit for reviews.

 2015-06-19 10:13 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
 Great, thanks for doing this! I'm afraid even if you succeed with patch we
 would still need more real-world examples that show the need for this
 feature, and I think this is separate from GHC tests, as they don't need to
 be realistic, but of course please continue and hopefully more examples will
 come.

 19 черв. 2015 16:19 Ömer Sinan Ağacan omeraga...@gmail.com пише:

 Done: https://ghc.haskell.org/trac/ghc/ticket/10547

 2015-06-19 9:12 GMT-04:00 Richard Eisenberg e...@cis.upenn.edu:
  Don't forget to make a Feature Request on Trac
  (https://ghc.haskell.org/trac/ghc/newticket) with a link to the wiki page.
  Trac is really the only way things like this don't get lost.
 
  Thanks!
 
  Richard
 
 
  On Jun 19, 2015, at 9:07 AM, Ömer Sinan Ağacan omeraga...@gmail.com
  wrote:
 
  Great, thanks Kostiantyn! I'm looking for simple examples that we can
  add to GHC testsuite, if I find something I'll update the wiki page
  also.
 
  I made some progress on the patch, I think I can hopefully submit
  something this weekend for reviews.
 
  2015-06-19 5:16 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
  Created some initial wiki-page with just one example, will keep it in
  mind
  to add more as seen.
 
 
  https://wiki.haskell.org/Expanding_type_synonyms_in_error_messages_proposal
 
  On Fri, Jun 19, 2015 at 10:42 AM, Simon Peyton Jones
  simo...@microsoft.com
  wrote:
 
  On this thread, a representative collection of *reproducible
  examples*
  with the actual error message and the desired one, would be
  tremendously
  helpful.  Lacking that, it’s hard to know where to begin.   (Creating
  the
  examples takes a bit of work, I know.)
 
 
 
  Start a wiki page!  Stuff in email threads gets lost
 
 
 
  Simon
 
 
 
  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of
  Christopher Allen
  Sent: 19 June 2015 04:27
  To: Ömer Sinan Ağacan
  Cc: ghc-devs
  Subject: Re: expanding type synonyms in error messages
 
 
 
  Just to add my own +1, having this when working with streaming
  libraries
  (I've needed it less with lens, oddly) would be a tremendous help for
  people
  learning them I think. I think I've run into the same thing as
  Kostiantyn in
  the past.
 
 
 
  On Thu, Jun 18, 2015 at 9:42 PM, Ömer Sinan Ağacan
  omeraga...@gmail.com
  wrote:
 
  It's good to see that I'm not the only one who wants this. I'm doing
  some GHC hacking nowadays and I'll give it a try.
 
 
  2015-06-18 4:41 GMT-04:00 Kostiantyn Rybnikov k...@k-bx.com:
  I wanted to add that synonym expansion would be especially helpful
  in
  error-messages like:
 
  Expected type: non-expanded, small type, like Producer a m ()
  Actual type: your type, like Proxy a a' b b' m v
 
  I would be glad if we could have an expansions enabling flag in GHC,
  and
  could consider turning it on by default if it will look good for
  that.
 
  16 черв. 2015 22:44 Richard Eisenberg e...@cis.upenn.edu пише:
 
  GHC tries hard to preserve type synonyms where possible, but of
  course,
  it
  can't preserve all of them. The general rule it tries to follow is:
  preserve
  vanilla type synonyms; expand type families. This is true both in
  expected
  types and actual types.
  If you have a case where you believe that GHC could preserve a type
  synonym in an expected type, submit a bug report. (Note that
  constraint
  synonyms are particularly hard to preserve!)
 
  It would be very easy to report both the synonym-preserving form
  and
  the
  expanded form in an error report, at the cost of making error
  reports
  even
  more verbose. You're welcome to submit a feature request, and this
  would
  likely make a good first patch to GHC if you want to get your hands
  dirty.
  I'd personally prefer the feature to be protected behind a flag (to
  avoid
  seeing that `String` expands to `[Char]` everywhere, for example),
  but
  others may feel differently here.
 
  Richard
 
  On Jun 16, 2015, at 11:20 AM, Ömer Sinan Ağacan
  omeraga...@gmail.com
  wrote:
 
  Hi all,
 
  While working with complex types with lots of arguments etc.
  errors

expanding type synonyms in error messages

2015-06-16 Thread Ömer Sinan Ağacan
Hi all,

While working with complex types with lots of arguments etc. errors are
becoming annoying very fast. For example, GHC prints errors in this way:

Expected type: type without any synonyms
  Actual type: type with synonyms

Now I have to expand that synonym in my head to understand the error.

I was wondering if implementing something like this is possible:

In type error messages, GHC also prints types that are cleaned from type
synonyms. Maybe something like this:

 Expected type: type1
(without synonyms): type1, synonyms are expanded
   Actual type: type2
(without synonyms): type2, synonyms are expanded

If this is not always desirable for some reason, we can hide this behavior
behind a flag.

What do GHC devs think about this? Is this, in theory, possible to do? How hard
would it be to implement this?

Thanks.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: question about GHC API on GHC plugin

2015-08-22 Thread Ömer Sinan Ağacan
 I have a new question: I'm working on supporting literals now.  I'm having
 trouble creating something that looks like `(App (Var F#) (Lit 1.0))` because
 I don't know how to create a variable that corresponds to the `F#`
 constructor.  The mkWiredInName function looks promising, but overly
 complicated.  Is this the correct function?  If so, what do I pass in for the
 Module, Unique, TyThing, and BuiltInSyntax parameters?

mkConApp intDataCon [mkIntLit dynFlags PUT_YOUR_INTEGER HERE]
mkConApp floatDataCon [mkFloatLit dynFlags PUT_YOUR_FLOAT_HERE]

Similarly for other literals...
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


How is this Generic-based instance implementation optimized by GHC?

2015-08-22 Thread Ömer Sinan Ağacan
Hi all,

I'm very confused by an optimization GHC is doing. I have this code:


data Tree a = Leaf a | Branch (Tree a) (Tree a)
  deriving (Generic, Show, NFData)

data Tree1 a = Leaf1 a | Branch1 (Tree1 a) (Tree1 a)
  deriving (Show)

instance NFData a = NFData (Tree1 a) where
  rnf (Leaf1 a) = rnf a
  rnf (Branch1 t1 t2) = rnf t1 `seq` rnf t2


When I benchmarked rnf calls I realized that they're too close, and I looked at
simplifier outputs. I believe these are relevant parts:

Rec {
Main.$fNFDataTree_$crnf [Occ=LoopBreaker]
  :: forall a_ab5v. NFData a_ab5v = Tree a_ab5v - ()
Main.$fNFDataTree_$crnf =
  \ (@ a17_ab5v)
($dNFData_ab5w :: NFData a17_ab5v)
(eta_B1 :: Tree a17_ab5v) -
case eta_B1 of _ [Occ=Dead] {
  Leaf g1_aaHO -
($dNFData_ab5w
 `cast` (Control.DeepSeq.NTCo:NFData[0] a17_ab5v_N
 :: NFData a17_ab5v ~R# (a17_ab5v - (
  g1_aaHO;
  Branch g1_aaHP g2_aaHQ -
case Main.$fNFDataTree_$crnf @ a17_ab5v $dNFData_ab5w g1_aaHP
of _ [Occ=Dead] { () -
Main.$fNFDataTree_$crnf @ a17_ab5v $dNFData_ab5w g2_aaHQ
}
}
end Rec }

Rec {
Main.$fNFDataTree1_$crnf [Occ=LoopBreaker]
  :: forall a_abd4. NFData a_abd4 = Tree1 a_abd4 - ()
Main.$fNFDataTree1_$crnf =
  \ (@ a17_abd4)
($dNFData_abd5 :: NFData a17_abd4)
(eta_B1 :: Tree1 a17_abd4) -
case eta_B1 of _ [Occ=Dead] {
  Leaf1 a18_a4tg -
($dNFData_abd5
 `cast` (Control.DeepSeq.NTCo:NFData[0] a17_abd4_N
 :: NFData a17_abd4 ~R# (a17_abd4 - (
  a18_a4tg;
  Branch1 t1_a4th t2_a4ti -
case Main.$fNFDataTree1_$crnf @ a17_abd4 $dNFData_abd5 t1_a4th
of _ [Occ=Dead] { () -
Main.$fNFDataTree1_$crnf @ a17_abd4 $dNFData_abd5 t2_a4ti
}
}
end Rec }

First one is generated by GHC and second one is hand-written. If you compare,
you'll see that they're identical. This looks like some serious magic, because
first one is generated from a default method that uses Generic methods and
types. Does anyone know how is that possible? Which optimization passes are
involved in this?

Thanks.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: How is this Generic-based instance implementation optimized by GHC?

2015-08-22 Thread Ömer Sinan Ağacan
Awesome, thanks for the pointer, Pedro.

2015-08-22 19:01 GMT-04:00 José Pedro Magalhães drei...@gmail.com:
 Hi there,

 GHC can often do a pretty good job at optimising generics. I wrote a paper
 that looks at that in detail:

 José Pedro Magalhães. Optimisation of Generic Programs through Inlining. In
 24th Symposium on Implementation and Application of Functional Languages
 (IFL'12), 2013.
 http://dreixel.net/research/pdf/ogpi.pdf


 Cheers,
 Pedro

 On Sat, Aug 22, 2015 at 11:26 PM, Ömer Sinan Ağacan omeraga...@gmail.com
 wrote:

 Hi all,

 I'm very confused by an optimization GHC is doing. I have this code:


 data Tree a = Leaf a | Branch (Tree a) (Tree a)
   deriving (Generic, Show, NFData)

 data Tree1 a = Leaf1 a | Branch1 (Tree1 a) (Tree1 a)
   deriving (Show)

 instance NFData a = NFData (Tree1 a) where
   rnf (Leaf1 a) = rnf a
   rnf (Branch1 t1 t2) = rnf t1 `seq` rnf t2


 When I benchmarked rnf calls I realized that they're too close, and I
 looked at
 simplifier outputs. I believe these are relevant parts:

 Rec {
 Main.$fNFDataTree_$crnf [Occ=LoopBreaker]
   :: forall a_ab5v. NFData a_ab5v = Tree a_ab5v - ()
 Main.$fNFDataTree_$crnf =
   \ (@ a17_ab5v)
 ($dNFData_ab5w :: NFData a17_ab5v)
 (eta_B1 :: Tree a17_ab5v) -
 case eta_B1 of _ [Occ=Dead] {
   Leaf g1_aaHO -
 ($dNFData_ab5w
  `cast` (Control.DeepSeq.NTCo:NFData[0] a17_ab5v_N
  :: NFData a17_ab5v ~R# (a17_ab5v - (
   g1_aaHO;
   Branch g1_aaHP g2_aaHQ -
 case Main.$fNFDataTree_$crnf @ a17_ab5v $dNFData_ab5w g1_aaHP
 of _ [Occ=Dead] { () -
 Main.$fNFDataTree_$crnf @ a17_ab5v $dNFData_ab5w g2_aaHQ
 }
 }
 end Rec }

 Rec {
 Main.$fNFDataTree1_$crnf [Occ=LoopBreaker]
   :: forall a_abd4. NFData a_abd4 = Tree1 a_abd4 - ()
 Main.$fNFDataTree1_$crnf =
   \ (@ a17_abd4)
 ($dNFData_abd5 :: NFData a17_abd4)
 (eta_B1 :: Tree1 a17_abd4) -
 case eta_B1 of _ [Occ=Dead] {
   Leaf1 a18_a4tg -
 ($dNFData_abd5
  `cast` (Control.DeepSeq.NTCo:NFData[0] a17_abd4_N
  :: NFData a17_abd4 ~R# (a17_abd4 - (
   a18_a4tg;
   Branch1 t1_a4th t2_a4ti -
 case Main.$fNFDataTree1_$crnf @ a17_abd4 $dNFData_abd5 t1_a4th
 of _ [Occ=Dead] { () -
 Main.$fNFDataTree1_$crnf @ a17_abd4 $dNFData_abd5 t2_a4ti
 }
 }
 end Rec }

 First one is generated by GHC and second one is hand-written. If you
 compare,
 you'll see that they're identical. This looks like some serious magic,
 because
 first one is generated from a default method that uses Generic methods and
 types. Does anyone know how is that possible? Which optimization passes
 are
 involved in this?

 Thanks.
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Forcing a linking error?

2015-08-14 Thread Ömer Sinan Ağacan
Here's an example that fails with a link time error when -threaded is not used:

➜  rts_test  ghc --make Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )
Linking Main ...
Main.o: In function `rn4_info':
(.text+0x26): undefined reference to `wakeUpRts'
collect2: error: ld returned 1 exit status

With -threaded it works:

➜  rts_test  ghc --make Main.hs -threaded
Linking Main ...

Code:

➜  rts_test  cat Main.hs
{-# LANGUAGE ForeignFunctionInterface #-}

module Main where

foreign import ccall wakeUpRts wakeUpRts :: IO ()

main :: IO ()
main = return ()

What I did is basically I found a function in GHC RTS that is only defined when
THREADED_RTS is defined and referred to it in my program.

2015-08-14 3:59 GMT-04:00 Erik de Castro Lopo mle...@mega-nerd.com:
 Dear ghc-devs,

 There is a commonly used library which has at least one function
 that when compiled into a program, requires the threaded run time
 system. Without the threaded runtime, the program just hangs.

 One kludgy solution to this problem is to have the function check
 for Control.Concurrent.rtsSupportsBoundThreads being true and
 throwing an error if its not. However, it would be much nicer if
 this could be turned into a link time error.

 Anyone have any ideas how this might be done?

 Cheers,
 Eri
 --
 --
 Erik de Castro Lopo
 http://www.mega-nerd.com/
 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Deleting sync-all

2015-07-21 Thread Ömer Sinan Ağacan
+1 from me. I only use it for `get` command after changing branches,
and I think I can just as easily do same thing with `git submodule
update --checkout`. (is that right?)

2015-07-21 6:45 GMT-04:00 Thomas Miedema thomasmied...@gmail.com:
 Hello ghc-devs,

 I would like to delete the file sync-all from the GHC repository. It should
 not have been necessary to use it for about a year now.

 To get the sources:

git clone --recursive git://git.haskell.org/ghc.git
cd ghc
git clone git://git.haskell.org/ghc-tarballs.git # Windows only


 To update an existing tree:
git pull --rebase

git submodule update --init


 To update an existing tree, without the possibility to forget to run `git
 submodule update --init`:
git config --global alias.pullall '!f(){ git pull --ff-only $@  git
 submodule update --init --recursive; }; f' # Run once
git pullall --rebase


 Please speak up if you want those 1000 lines of buggy Perl a.k.a. sync-all
 to stay for some reason, or if you have questions about a certain git
 submodules workflow.


 The source code (./boot no longer suggests it) and the wiki are already
 sync-all free, except for a few historical pages.

 Discussion period: 1 month.


 Thomas



 ___
 ghc-devs mailing list
 ghc-devs@haskell.org
 http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Segfault in a CoreLinted program (and a GHC-generated Core question)

2015-10-26 Thread Ömer Sinan Ağacan
OK, thanks to people at IRC channel(especially @rwbarton) I realized
that my lint calls were not actually running, simply because I wasn't
using -dcore-lint.. I didn't know such a flag exists, and even with
the absence of the flag I'd expect a core lint would work, because I'm
explicitly calling the lint function without checking any flags!

CoreLint is now giving me really awesome diagnostics! Sorry for the noise..

(I'll try to document linter functions or CoreLint module to let the
user know he/she needs this flag!)

2015-10-26 13:43 GMT-04:00 Simon Peyton Jones :
> |  So my questions are: Am I right in assuming that CoreLint accepted programs
> |  should not segfault?
>
> Yes.  Modulo unsafeCoerce, and FFI calls.
>
> | What about internal invariants? Should CoreLint check
> |  for those? Is there any pass that checks for invariants and prints helpful
> |  messages in case of a invariant invalidation?
>
> Yes; they are documented in CoreSyn, which the data type, and Lint checks 
> them.
>
> |  As an attempt at debugging the code generated by my plugin, I wrote the
> |  function that is supposed to be generated by my Core pass in Haskell and
> |  compiled with GHC. Generated Core is mostly the same, except at one point 
> it
> |  has an extra lambda directly applied to a void#, something like ((\_ -> 
> ...)
> |  void#). Where can I learn more about why GHC is doing that?
>
> Show me the code!
>
> Instead of generating
>
> x :: Int# = 
>
> GHC sometimes generates
>
> x :: Void# -> Int# = \_ - 
>
> and then calls (x void#), to make any div-zero failures happen at the right 
> place.
>
> I'm not sure if that is what you are seeing, but we can work it out when you 
> give more detail.
>
> Simon
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Segfault in a CoreLinted program (and a GHC-generated Core question)

2015-10-26 Thread Ömer Sinan Ağacan
I have a very simple Core plugin that generates some functions. After my
Core-to-Core pass is done, I'm running the linter to make sure the Core
generated by my plugin is well-formed and well-typed. However, even though lint
checker passes, the code generated by my plugin is failing with a segfault.

I created a git repo for demonstration: https://github.com/osa1/plugins

This is where the CoreLint is happening:
https://github.com/osa1/plugins/blob/master/src/Plugins.hs#L38

I'm using GHC HEAD(it doesn't build with 7.10). Here's how to run:

Make sure GHC HEAD is in the $PATH, then

$ cabal install --with-ghc=ghc-stage2
$ cd test

Adding bunch of -ddump parameters here for debugging purposes:

$ ghc-stage2 -fplugin=Plugins --make Main.hs -fforce-recomp
-ddump-simpl -ddump-ds -ddump-to-file -ddump-stg

Now if you run the generated program, it should first print some numbers and
then segfault.

---

I heard from Simon in various talks(e.g. Haskell exchange 2015) that if lint
passes, then there should be no segfaults, so I thought this should be a bug.
I'm actually having some other problems with CoreLint too, for example, even
though Core lint passes, if I run Core simplifier pass after my plugin runs,
GHC is failing with various different panics. Some of those panics are
happening inside STG generation, not in simplifier(but it works fine if I
disable the simplifier!) It seems like CoreLint is not strict enough, it's not
checking some invariants that GHC simplifier and STG code generator are
assuming.

So my questions are: Am I right in assuming that CoreLint accepted programs
should not segfault? What about internal invariants? Should CoreLint check for
those? Is there any pass that checks for invariants and prints helpful messages
in case of a invariant invalidation?

As an attempt at debugging the code generated by my plugin, I wrote the
function that is supposed to be generated by my Core pass in Haskell and
compiled with GHC. Generated Core is mostly the same, except at one point it
has an extra lambda directly applied to a void#, something like ((\_ -> ...)
void#). Where can I learn more about why GHC is doing that?

Thanks.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: How inline pragma works

2015-11-10 Thread Ömer Sinan Ağacan
There's this section in GHC user manual:
https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/pragmas.html#inline-noinline-pragma

But see also: https://ghc.haskell.org/trac/ghc/ticket/10766

2015-11-10 5:16 GMT-05:00 Эдгар Жаворонков :
> Hello everyone!
>
> Where can i read about how does INLINE pragma in compiler works?
>
>
> ---
> С уважением,
> Жаворонков Эдгар
>
> Best regards,
> Edgar A. Zhavoronkov
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: How inline pragma works

2015-11-10 Thread Ömer Sinan Ağacan
I don't know the whole story, but here are some pointers to get you started:

- Internally, inlined code is called "unfolding". You can see the definition in
  CoreSyn.

- CoreUnfold module has important functions to decide whether to inline or not.

- Actual work of replacing identifiers with their definitions is done in
  Simplify and probably in some other places.

I believe if you start grepping for functions in CoreUnfold you can find all
the places that inlining is done. It may be just the simplifier, I'm not sure.
(see SimplUtils.preInlineUnconditionally and
SimplUtils.postInlineUnconditionally)

When you figure the details it'd be great if you could give us a hand in #10766
:)

2015-11-10 15:57 GMT-05:00 Эдгар Жаворонков <edzhavoron...@gmail.com>:
> And can you tell me, where can i find a source code in GHC to see, how this
> pragma is handeled?
>
> ---
> С уважением,
> Жаворонков Эдгар
>
> Best regards,
> Edgar A. Zhavoronkov
>
> 2015-11-10 17:48 GMT+03:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
>>
>> There's this section in GHC user manual:
>>
>> https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/pragmas.html#inline-noinline-pragma
>>
>> But see also: https://ghc.haskell.org/trac/ghc/ticket/10766
>>
>> 2015-11-10 5:16 GMT-05:00 Эдгар Жаворонков <edzhavoron...@gmail.com>:
>> > Hello everyone!
>> >
>> > Where can i read about how does INLINE pragma in compiler works?
>> >
>> >
>> > ---
>> > С уважением,
>> > Жаворонков Эдгар
>> >
>> > Best regards,
>> > Edgar A. Zhavoronkov
>> >
>> > ___
>> > ghc-devs mailing list
>> > ghc-devs@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>> >
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: too many lines too long

2015-11-09 Thread Ömer Sinan Ağacan
I also dislike the idea of automatically rejecting such code. I agree with
Austin's argument that the contribution barrier is already too high and
Richard's arguments, but in addition to those, I think it wouldn't be fair
because some patches of people with push access won't be subject to the
automatic lint checks. 100-col lines will make it to the code base even if only
by mistake. It'll be annoying to new contributors and won't solve the problem.

Personally I'm trying to be very careful, and in my patches I usually do a lint
pass at the end to fix all long lines. But I'm OK if some patches with 100-col
lines occasionally make it to the master.

2015-11-09 16:21 GMT-05:00 Richard Eisenberg :
> I agree that being forceful about the 80-col limit would solve my problem.
>
> But I really dislike the idea. There will always be long-running patches. 
> Volunteers can't be relied on to have time available to continue their work 
> right away. And so I think this decision would increase barriers to 
> contributing and increase merge conflicts for a cause that, frankly, isn't 
> terribly important. (To repeat: I *do* want 80-col lines. I just want an 
> amazing compiler more.)
>
> Richard
>
> On Nov 9, 2015, at 4:15 PM, Austin Seipp  wrote:
>
>> Something like this might be possible. It'd just require implementing
>> a new arcanist linter, I think, and enabling it in .arclint
>>
>> In general I really sympathize with this. The problem 90% of people
>> hit is that they touch a line that was *already* over 80 columns, so
>> 'arc lint' warns them and gets annoyed, but they don't want to fix or
>> split up a bunch of stuff to avoid it. It's an issue of having to do
>> 'boring work' which nobody likes, and seems very tedious, regardless
>> of the mechanism of how they do the change.
>>
>> Really, I'm more inclined to begin a policy of rejecting reviews that
>> do not pass the linter. Exceptions can be made, but in general we need
>> to start *enforcing it* with the red button I think. And it would
>> require us to be more diligent about merging patches quickly to reduce
>> the scope of merge conflicts (because fixing an 80col violation
>> normally, almost always, adds more LOC).
>>
>> However, there are people who in general think the contribution
>> barrier is already too high, and I fear that enforcing this with a
>> hard rule may make people 'give up' because it seems like a pointless
>> thing to mandate to block their changes. I'm not sure how people feel
>> about that, but it is worth keeping in mind the developer economics.
>>
>> I hope suggesting the possibility of being more forceful against 80col
>> violations doesn't derail this too much. :)
>>
>> On Mon, Nov 9, 2015 at 3:02 PM, Richard Eisenberg  wrote:
>>> Hi devs,
>>>
>>> We seem to be uncommitted to the ideal of 80-character lines. Almost every 
>>> patch on Phab I look through has a bunch of "line too long" lint errors. No 
>>> one seems to do much about these. And Phab's very very loud indication of a 
>>> lint error makes reviewing the code harder.
>>>
>>> I like the ideal of 80-character lines. I aim for this ideal in my patches, 
>>> falling short sometimes, of course. But I think the current setting of 
>>> requiring everyone to "explain" away their overlong lines during `arc diff` 
>>> and then trying hard to ignore the lint errors during code review is wrong. 
>>> And it makes us all inured to more serious lint errors.
>>>
>>> How about this: after `arc diff` is run, it will count the number of 
>>> overlong lines before and after the patch. If there are more after, have 
>>> the last thing `arc diff` outputs be a stern telling-off of the dev, along 
>>> the lines of
>>>
 Before your patch, 15 of the edited lines were over 80 characters.
 Now, a whopping 28 of them are. Can't you do better? Please?
>>>
>>> Would this be ignored more or followed more? Who knows. But it would sure 
>>> be less annoying. :)
>>>
>>> What do others think?
>>>
>>> Thanks,
>>> Richard
>>> ___
>>> ghc-devs mailing list
>>> ghc-devs@haskell.org
>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>>
>>
>>
>>
>> --
>> Regards,
>>
>> Austin Seipp, Haskell Consultant
>> Well-Typed LLP, http://www.well-typed.com/
>>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Implementation idea for unboxed polymorphic types

2015-11-15 Thread Ömer Sinan Ağacan
I had started working on exactly the same thing at some point. I had a
TemplateHaskell-based implementation which _almost_ worked.

The problem was that the syntax was very, very heavy. Because I had to use
quotes for _every_ constructor application(with explicitly passed types).
(because I had a specialized constructor for every instantiation of this
generic type)

Another problem was that because of how TemplateHaskell quotes evaluated, I
couldn't use a `List Int` where `List` is a template without first manually
adding a line for generating specialized version of `List` on `Int`.

When all of these combined it became very hard to use. But it was a
proof-of-concept and I think it worked.

(Code is horrible so I won't share it here :) I had to maintain a state shared
with different TH quote evaluations etc.)

2015-11-15 5:26 GMT-05:00 Francesco Mazzoli :
> (A nicely rendered version of this email can be found at 
> )
>
> ## Macro types
>
> I very often find myself wanting unboxed polymorphic types
> (e.g. types that contain `UNPACK`ed type variables). I find
> it extremely frustrating that it's easier to write fast _and_
> generic code in C++ than in Haskell.
>
> I'd like to submit to the mailing list a very rough proposal
> on how this could be achieved in a pretty straightforward way
> in GHC.
>
> The proposal is meant to be a proof of concept, just to show that
> this could be done rather easily. I did not think about a nice
> interface or the implementation details in GHC. My goal is to
> check the feasibility of this plan with GHC developers.
>
> I'll call such types "macro types", since their effect is similar
> to defining a macro that defines a new type for each type
> variable instantiation.
>
> Consider
>
> ```
> data #Point a = Point
>   { x :: {-# UNPACK #-} !a
>   , y :: {-# UNPACK #-} !a
>   }
> ```
>
> This definition defines the macro type `#Point`, with one parameter
> `a`.
>
> Macro types definition would be allowed only for single-constructor
> records. The intent is that if we mention `#Point Double`, it will
> be equivalent to
>
> ```
> data PointDouble = PointDouble
>   { x :: {-# UNPACK #-} !Double
>   , y :: {-# UNPACK #-} !Double
>   }
> ```
>
> To use `#Point` generically, the following type class would be
> generated:
>
> ```
> class PointFamily a where
>   data #Point a :: * -- Family of types generated by @data #Point a@.
>   #Point :: a -> a -> #Point a -- Constructor.
>   #x :: #Point a -> a -- Projection @x@.
>   #y :: #Point a -> a -- Projection @y@.
> ```
>
> Thi type class lets us work with `#Point`s generically, for example
>
> ```
> distance :: (PointFamily a, Fractional a) => #Point a -> #Point a -> a
> distance p1 p2 =
>   let dx = #x p1 - #x p2
>   dy = #y p1 - #y p2
>   in sqrt (dx*dx + dy*dy)
> ```
>
> Internally, for every type appearing for `a`, e.g. `#Point Double`,
> a new type equivalent to the `PointDouble` above would be generated
> by GHC, with the corresponding instance
>
> ```
> instance PointFamily Double where
>   data #Point Double = PointDouble
>   #x = x
>   #y = x
> ```
>
> If it's not possible to instantiate `#Point` with the provided type
> (for example because the type is not `UNPACK`able, e.g.
> `#Point (Maybe A)`), GHC would throw an error.
>
> Note that we can compile `distance` in its polymorphic version
> (as opposed to C++ templates, where template functions _must_ be
> instantiated at every use). The polymorphic `distance` would
> require a call to "virtual functions" `#x` and `#y`, as provided by
> the `PointFamily` dictionary. But if we use
> `INLINE` or `SPECIALIZE` pragmas the virtual calls to `#x` and `#y`
> would disappear, making this as efficient as if we were to define
> `distance` on the manually defined `PointDouble`. Compiler hints
> would be put in place to always inline functions using macro types,
> if possible.
>
> Note that the inlining is only important so that the `PointFamily`
> dictionary disappears, e.g. functions containing recursive
> helpers are fine, such as
>
> ```
> {-# INLINE leftmost #-}
> leftmost :: forall a. (PointFamily a, Ord a) => [#Point a] -> #Point a
> leftmost [] = error "leftmost: no points"
> leftmost (p0 : ps0) = go p0 ps0
>   where
> go :: #Point a -> [#Point a] -> Point# a
> go candidate (p : ps) =
>   if #x p < #x candidate
> then go p ps
> else go candidate ps
> ```
>
> It might be worth considering throwing a warning when a top-level
> definition whose type contains a macro type cannot be inlined, since
> the main performance benefit of using macro types would be lost.
>
> We can define instances for these types as normal, for instance
>
> ```
> instance (Show a, PointFamily a) => Show (#Point a) where
>   {-# INLINE show #-}
>   show pt = "Point{x = " ++ #x pt ++ ", y = " ++ #y pt ++ "}"
> ```
>
> `deriving` support could also be added.
>
> ## Further ideas
>
> ### Hide or remove 

Re: Implementation idea for unboxed polymorphic types

2015-11-16 Thread Ömer Sinan Ağacan
> But I don't see why you'd need quoting at constructor calls. Couldn't you
> just have a type class like `PointFamily`?

This is exactly right, my memory has failed me. My initial implementation
didn't use the type family trick, I had further attempts that use type families
but honestly I don't remember how good it worked. This was quite a while ago.

2015-11-15 19:41 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
> After reading Francesco's original post, I immediately thought of Ömer's 
> proposed approach, of using Template Haskell to produce the right data family 
> instances. But I don't see why you'd need quoting at constructor calls. 
> Couldn't you just have a type class like `PointFamily`? I'd be more 
> interested to see client code in Ömer's version than the TH generation code.
>
> The TH approach would seem to require having a fixed set of specializations, 
> which is a downside. But I'm not sure it's so much of a downside that the 
> approach is unusable.
>
> Richard
>
> On Nov 15, 2015, at 10:08 AM, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:
>
>> I had started working on exactly the same thing at some point. I had a
>> TemplateHaskell-based implementation which _almost_ worked.
>>
>> The problem was that the syntax was very, very heavy. Because I had to use
>> quotes for _every_ constructor application(with explicitly passed types).
>> (because I had a specialized constructor for every instantiation of this
>> generic type)
>>
>> Another problem was that because of how TemplateHaskell quotes evaluated, I
>> couldn't use a `List Int` where `List` is a template without first manually
>> adding a line for generating specialized version of `List` on `Int`.
>>
>> When all of these combined it became very hard to use. But it was a
>> proof-of-concept and I think it worked.
>>
>> (Code is horrible so I won't share it here :) I had to maintain a state 
>> shared
>> with different TH quote evaluations etc.)
>>
>> 2015-11-15 5:26 GMT-05:00 Francesco Mazzoli <f...@mazzo.li>:
>>> (A nicely rendered version of this email can be found at 
>>> <https://gist.github.com/bitonic/52cfe54a2dcdbee1b7f3>)
>>>
>>> ## Macro types
>>>
>>> I very often find myself wanting unboxed polymorphic types
>>> (e.g. types that contain `UNPACK`ed type variables). I find
>>> it extremely frustrating that it's easier to write fast _and_
>>> generic code in C++ than in Haskell.
>>>
>>> I'd like to submit to the mailing list a very rough proposal
>>> on how this could be achieved in a pretty straightforward way
>>> in GHC.
>>>
>>> The proposal is meant to be a proof of concept, just to show that
>>> this could be done rather easily. I did not think about a nice
>>> interface or the implementation details in GHC. My goal is to
>>> check the feasibility of this plan with GHC developers.
>>>
>>> I'll call such types "macro types", since their effect is similar
>>> to defining a macro that defines a new type for each type
>>> variable instantiation.
>>>
>>> Consider
>>>
>>> ```
>>> data #Point a = Point
>>>  { x :: {-# UNPACK #-} !a
>>>  , y :: {-# UNPACK #-} !a
>>>  }
>>> ```
>>>
>>> This definition defines the macro type `#Point`, with one parameter
>>> `a`.
>>>
>>> Macro types definition would be allowed only for single-constructor
>>> records. The intent is that if we mention `#Point Double`, it will
>>> be equivalent to
>>>
>>> ```
>>> data PointDouble = PointDouble
>>>  { x :: {-# UNPACK #-} !Double
>>>  , y :: {-# UNPACK #-} !Double
>>>  }
>>> ```
>>>
>>> To use `#Point` generically, the following type class would be
>>> generated:
>>>
>>> ```
>>> class PointFamily a where
>>>  data #Point a :: * -- Family of types generated by @data #Point a@.
>>>  #Point :: a -> a -> #Point a -- Constructor.
>>>  #x :: #Point a -> a -- Projection @x@.
>>>  #y :: #Point a -> a -- Projection @y@.
>>> ```
>>>
>>> Thi type class lets us work with `#Point`s generically, for example
>>>
>>> ```
>>> distance :: (PointFamily a, Fractional a) => #Point a -> #Point a -> a
>>> distance p1 p2 =
>>>  let dx = #x p1 - #x p2
>>>  dy = #y p1 - #y p2
>>>  in sqrt (dx*dx + dy*dy)
>>> ```
>>>
>>> Internally, for every type ap

Printing local Var(Id) types(in Outputable outputs)

2015-11-05 Thread Ömer Sinan Ağacan
Hi all,

I'm considering getting into the trouble of implementing this: A flag for
printing types of local Ids. To be more specific, I'd like to see types of
local Ids and binders in case expression alternatives etc. I may name it
-dshow-local-id-types or something like that.

An example output would be like this. Instead of:

  case ds_dPC of _ [Occ=Dead] {
C1 l_avq -> ...
C2 r_avr -> ...
  }

It would print:

  case ds_dPC of _ [Occ=Dead] {
C1 (l_avq :: Type1) -> ...
C2 (r_avr :: Type2) -> ...
  }

So my questions are:

* Do we already have something like this? (I can't see it in man page)

* Do you think, for some reason, this would be useless? (maybe there's some
  workaround etc. that has a similar effect)

Thanks.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


is this change in TH error message intentional?

2015-10-19 Thread Ömer Sinan Ağacan
Hi all,

I realized this change in TH error messages:

GHC 7.10.2:

➜  th-test  ghc --make Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )

Main.hs:13:15:
Not in scope: ‘locaton’
Perhaps you meant ‘location’ (imported from Language.Haskell.TH.Syntax)
In the splice: $locaton

Main.hs:13:15:
GHC stage restriction:
  ‘locaton’ is used in a top-level splice or annotation,
  and must be imported, not defined locally
In the expression: locaton
In the splice: $locaton

I think both error messages are quite useful in this context. I don't see
second one as redundant.

However, with HEAD:

➜  th-test  ghc-stage2 --make Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )

Main.hs:13:15: error:
Variable not in scope: locaton :: ExpQ
Perhaps you meant ‘location’ (imported from Language.Haskell.TH.Syntax)

I think this new message is quite worse than previous one. First, "In the
splice ..." part is missing. Second, "It must be imported, not defined locally"
message is not given at all.

Was this change intentional? May I ask why it's changed?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Building stage1 only

2015-10-19 Thread Ömer Sinan Ağacan
(I know I asked this many times in IRC channel but I don't remember getting any
answers. I apologize if anyone had answered this on IRC channel and I missed)

With current build system, even if I choose "devel1" it always builds stage2
compiler too. A comment in build.mk says that it's for working on stage1
compiler, so I'd expect it to build only stage1.

The reason I want stage1-only builds is the time it takes to build both stages.
It takes approximately 30 minutes and if I could reduce this down to half that
would greatly improve my work flow.

Most of the time I don't need a full build, but in my experience, it's very
easy to end up in a state where `make` simply can't build, and only
easy fix is a
`make clean`, which costs 30 minutes because then I have to build from scratch.
This happens way too often, and so I need a stage1-only build.

Thanks..
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Show instances for GHC internals

2015-10-19 Thread Ömer Sinan Ağacan
Currently the only way to debug and inspect GHC internals is by adding some
carefully placed print statements. (I'd love to be proven wrong on this, cost
of debugging this way is huge, given how long it's taking to rebuild GHC)

We have Outputable instances for most data types, and `Outputable.pprTrace`
etc. helps with debugging/inspecting pure functions this way.

However, Outputable instances are hiding some details and they're sometimes not
useful for debugging and inspecting internals. This is why I implemented
CoreDump package(http://hackage.haskell.org/package/CoreDump), Outputable
instance of CoreSyn is simply not useful for some things. Similarly, just today
I had to add a show function for `HscTypes.TargetId` because `Outputable`
instance was hiding `Maybe Phase` field.

Since the only way to debug or inspect GHC internals(except maybe the RTS) is
by printing things, I think we should provide Show instances for.. basically
everything. Otherwise I just can't see a way of debugging things and inspecting
internals, tracing code etc. for learning purposes.

I was wondering what would be the cost of adding Show instances. Would that
mean significantly increased compile times? Or significantly bigger GHC
binaries? If that's the case, could we enable Show instances with some
arguments so that we can enable/disable it by modifying mk/build.mk?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: is this change in TH error message intentional?

2015-10-20 Thread Ömer Sinan Ağacan
Originally I had this file:

{-# LANGUAGE TemplateHaskell #-}

module Main where

import Language.Haskell.TH
import Language.Haskell.TH.Syntax

-- import LiftLoc

main :: IO ()
main = do
  let loc :: Loc
  loc = $(locaton)
  -- loc = $(locaton >>= lift)
  print loc

But any code with a undefined name inside TH splice would work, I think:

{-# LANGUAGE TemplateHaskell #-}
module Main where
import Language.Haskell.TH
main = print $(blah)



➜  th-test  ghc --make Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )

Main.hs:10:16:
Not in scope: ‘blah’
In the splice: $blah

Main.hs:10:16:
GHC stage restriction:
  ‘blah’ is used in a top-level splice or annotation,
  and must be imported, not defined locally
In the expression: blah
In the splice: $blah

➜  th-test  ghc-stage2 --make Main.hs
[1 of 1] Compiling Main ( Main.hs, Main.o )

Main.hs:10:16: error: Variable not in scope: blah :: ExpQ

2015-10-20 2:04 GMT-04:00 Jan Stolarek <jan.stola...@p.lodz.pl>:
> Ömer, can you show us the source of Main.hs?
>
> Janek
>
> Dnia poniedziałek, 19 października 2015, Ömer Sinan Ağacan napisał:
>> Hi all,
>>
>> I realized this change in TH error messages:
>>
>> GHC 7.10.2:
>>
>> ➜  th-test  ghc --make Main.hs
>> [1 of 1] Compiling Main ( Main.hs, Main.o )
>>
>> Main.hs:13:15:
>> Not in scope: ‘locaton’
>> Perhaps you meant ‘location’ (imported from
>> Language.Haskell.TH.Syntax) In the splice: $locaton
>>
>> Main.hs:13:15:
>> GHC stage restriction:
>>   ‘locaton’ is used in a top-level splice or annotation,
>>   and must be imported, not defined locally
>> In the expression: locaton
>> In the splice: $locaton
>>
>> I think both error messages are quite useful in this context. I don't see
>> second one as redundant.
>>
>> However, with HEAD:
>>
>> ➜  th-test  ghc-stage2 --make Main.hs
>> [1 of 1] Compiling Main ( Main.hs, Main.o )
>>
>> Main.hs:13:15: error:
>> Variable not in scope: locaton :: ExpQ
>> Perhaps you meant ‘location’ (imported from
>> Language.Haskell.TH.Syntax)
>>
>> I think this new message is quite worse than previous one. First, "In the
>> splice ..." part is missing. Second, "It must be imported, not defined
>> locally" message is not given at all.
>>
>> Was this change intentional? May I ask why it's changed?
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
>
> ---
> Politechnika Łódzka
> Lodz University of Technology
>
> Treść tej wiadomości zawiera informacje przeznaczone tylko dla adresata.
> Jeżeli nie jesteście Państwo jej adresatem, bądź otrzymaliście ją przez 
> pomyłkę
> prosimy o powiadomienie o tym nadawcy oraz trwałe jej usunięcie.
>
> This email contains information intended solely for the use of the individual 
> to whom it is addressed.
> If you are not the intended recipient or if you have received this message in 
> error,
> please notify the sender and delete it from your system.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Building stage1 only

2015-10-20 Thread Ömer Sinan Ağacan
> Out of sheer curiosity: in what situations does that happen for you? *If* you
> are working on a single branch, ie. you're not switching back and forth
> between master and your feature branches, this should not happen (and even if
> you switch between branches it should still be safe for most of the time).

I'm actually swtiching branches quite a lot, because most of the time I have
multiple tasks at hand, working on multiple tickets etc.

But I think there's another way to introduce this kind of failures. Since
compilation take very long, I never start the build process and wait until it's
done, I keep coding in the meantime. Maybe I should rsync changes manually to
another directory and run build there while I keep working on current tree etc.


I just tried `make 1` in ghc directory and I think it worked(I'll try on a
clean tree once I have to `make clean` and see if it's really building only
stage-1). But my next question is why marking it as such in build.mk doesn't
work.. I'd expect `devel1` to build stage1 only.

2015-10-20 3:12 GMT-04:00 Jan Stolarek :
>> it's very easy to end up in a state where `make` simply can't build, and only
>> easy fix is a `make clean`
> Out of sheer curiosity: in what situations does that happen for you? *If* you 
> are working on a
> single branch, ie. you're not switching back and forth between master and 
> your feature branches,
> this should not happen (and even if you switch between branches it should 
> still be safe for most
> of the time). Richard already gave you a trick (cd ghc/ && make 2) that 
> allows to build only
> stage 2 compiler without rebuilding stage 1 or any of the libraries. One 
> situation that comes to
> my mind that can really require a full rebuild is changing format of 
> interface files. But other
> than that you shouldn't have to do a full rebuild too often.
>
> I know how you feel. When I started working on GHC I had to do a full rebuild 
> very often. But now
> I improved my workflow and only do a full build after a major rebase of my 
> branch against master.
>
> Janek
>
> ---
> Politechnika Łódzka
> Lodz University of Technology
>
> Treść tej wiadomości zawiera informacje przeznaczone tylko dla adresata.
> Jeżeli nie jesteście Państwo jej adresatem, bądź otrzymaliście ją przez 
> pomyłkę
> prosimy o powiadomienie o tym nadawcy oraz trwałe jej usunięcie.
>
> This email contains information intended solely for the use of the individual 
> to whom it is addressed.
> If you are not the intended recipient or if you have received this message in 
> error,
> please notify the sender and delete it from your system.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Show instances for GHC internals

2015-10-20 Thread Ömer Sinan Ağacan
> One difficulty is that many of the core type data types, e.g. TyThing,
> are (1) a large mutually recursive graph, and (2) have
> unsafeInterleaveIO thunks which would induce IO action.  So a naive
> Show instance would give infinite output and have lots of side effects.
> There are many data types which could usefully have Show added but
> also many which would be very difficult to.

Ah, yes, this is a very annoying problem. I discovered that when I first wrote
CoreDump: https://github.com/osa1/CoreDump/issues/2

I don't have solution to this yet.

2015-10-19 21:59 GMT-04:00 Edward Z. Yang :
> Excerpts from Ömer Sinan Ağacan's message of 2015-10-19 14:18:41 -0700:
>> I was wondering what would be the cost of adding Show instances. Would that
>> mean significantly increased compile times? Or significantly bigger GHC
>> binaries? If that's the case, could we enable Show instances with some
>> arguments so that we can enable/disable it by modifying mk/build.mk?
>
> One difficulty is that many of the core type data types, e.g. TyThing,
> are (1) a large mutually recursive graph, and (2) have
> unsafeInterleaveIO thunks which would induce IO action.  So a naive
> Show instance would give infinite output and have lots of side effects.
> There are many data types which could usefully have Show added but
> also many which would be very difficult to.
>
> Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Show instances for GHC internals

2015-10-20 Thread Ömer Sinan Ağacan
> There are more interesting parts of your post, but I can respond to this: It
> shouldn't take that much time. Once you have ghc-stage2 built, you should be
> able to say `make 2` in the ./ghc subdirectory and get a new binary in a few
> seconds.
>
> Using `make 1` in the ./compiler subdirectory works similarly for the stage1
> compiler. But only once it's built the first time.

I replied this in other thread, I think it works but I'll make sure next time I
do a `make clean`. Thanks.



Another problem is this: Hiding fields of types is great for safety reasons,
but not so great for debugging.

In CoreDump I'm having this problems:

- Sometimes GHC can't derive Show instance because record fields are hidden.
  But every field is actually exposed in a read-only way with some manually
  defined functions. This is super annoying. It'd be really awesome if we could
  export record fields as "read-only". (very half-baked idea)

- Sometimes fields are hidden, and no accessors are provided. This is even
  worse because now there's really no way to derive Show, using `deriving` or
  manually.

> (2) have unsafeInterleaveIO thunks which would induce IO action

Edward, do you remember any examples of such code?

2015-10-20 9:22 GMT-04:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
>> One difficulty is that many of the core type data types, e.g. TyThing,
>> are (1) a large mutually recursive graph, and (2) have
>> unsafeInterleaveIO thunks which would induce IO action.  So a naive
>> Show instance would give infinite output and have lots of side effects.
>> There are many data types which could usefully have Show added but
>> also many which would be very difficult to.
>
> Ah, yes, this is a very annoying problem. I discovered that when I first wrote
> CoreDump: https://github.com/osa1/CoreDump/issues/2
>
> I don't have solution to this yet.
>
> 2015-10-19 21:59 GMT-04:00 Edward Z. Yang <ezy...@mit.edu>:
>> Excerpts from Ömer Sinan Ağacan's message of 2015-10-19 14:18:41 -0700:
>>> I was wondering what would be the cost of adding Show instances. Would that
>>> mean significantly increased compile times? Or significantly bigger GHC
>>> binaries? If that's the case, could we enable Show instances with some
>>> arguments so that we can enable/disable it by modifying mk/build.mk?
>>
>> One difficulty is that many of the core type data types, e.g. TyThing,
>> are (1) a large mutually recursive graph, and (2) have
>> unsafeInterleaveIO thunks which would induce IO action.  So a naive
>> Show instance would give infinite output and have lots of side effects.
>> There are many data types which could usefully have Show added but
>> also many which would be very difficult to.
>>
>> Edward
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


build system issue: some changes in libraries doesn't trigger required rebuilds

2015-11-14 Thread Ömer Sinan Ağacan
Hi all,

I'm having this annoying issue all the time: Whenever a `git pull origin
master` updates a library(one of the submodules, like `Binary`) a `make`
doesn't trigger required rebuilds(e.g. it doesn't rebuild libraries and tries
to rebuild GHC code).

I don't know how to force build libraries, so most of the time I end up doing
`make distclean` and wasting 30 minutes.

I was wondering if there's a way to force rebuilding libraries? Or can we fix
the build system somehow?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: question about GHC API on GHC plugin

2015-08-25 Thread Ömer Sinan Ağacan
It seems like in your App syntax you're having a non-function in function
position. You can see this by looking at what failing function
(splitFunTy_maybe) is doing:

splitFunTy_maybe :: Type - Maybe (Type, Type)
-- ^ Attempts to extract the argument and result types from a type
... (definition is not important) ...

Then it's used like this at the error site:

(arg_ty, res_ty) = expectJust cpeBody:collect_args $
   splitFunTy_maybe fun_ty

In your case this function is returning Nothing and then exceptJust is
signalling the panic.

Your code looked correct to me, I don't see any problems with that. Maybe you're
using something wrong as selectors. Could you paste CoreExpr representation of
your program?

It may also be the case that the panic is caused by something else, maybe your
syntax is invalidating some assumptions/invariants in GHC but it's not
immediately checked etc. Working at the Core level is frustrating at times.

Can I ask what kind of plugin are you working on?

(Btw, how did you generate this representation of AST? Did you write it
manually? If you have a pretty-printer, would you mind sharing it?)

2015-08-25 18:50 GMT-04:00 Mike Izbicki m...@izbicki.me:
 Thanks Ömer!

 I'm able to get dictionaries for the superclasses of a class now, but
 I get an error whenever I try to get a dictionary for a
 super-superclass.  Here's the Haskell expression I'm working with:

 test1 :: Floating a = a - a
 test1 x1 = x1+x1

 The original core is:

 + @ a $dNum_aJu x1 x1

 But my plugin is replacing it with the core:

 + @ a ($p1Fractional ($p1Floating $dFloating_aJq)) x1 x1

 The only difference is the way I'm getting the Num dictionary.  The
 corresponding AST (annotated with variable names and types) is:

 App
 (App
 (App
 (App
 (Var +::forall a. Num a = a - a - a)
 (Type a)
 )
 (App
 (Var $p1Fractional::forall a. Fractional a = Num a)
 (App
 (Var $p1Floating::forall a. Floating a = Fractional a)
 (Var $dFloating_aJq::Floating a)
 )
 )
 )
 (Var x1::'a')
 )
 (Var x1::'a')

 When I insert, GHC gives the following error:

 ghc: panic! (the 'impossible' happened)
   (GHC version 7.10.1 for x86_64-unknown-linux):
 expectJust cpeBody:collect_args

 What am I doing wrong with extracting these super-superclass
 dictionaries?  I've looked up the code for cpeBody in GHC, but I can't
 figure out what it's trying to do, so I'm not sure why it's failing on
 my core.

 On Mon, Aug 24, 2015 at 7:10 PM, Ömer Sinan Ağacan omeraga...@gmail.com 
 wrote:
 Mike, here's a piece of code that may be helpful to you:

 https://github.com/osa1/sc-plugin/blob/master/src/Supercompilation/Show.hs

 Copy this module to your plugin, it doesn't have any dependencies other than
 ghc itself. When your plugin is initialized, update `dynFlags_ref` with your
 DynFlags as first thing to do. Then use Show instance to print AST directly.

 Horrible hack, but very useful for learning purposes. In fact, I don't know 
 how
 else we can learn what Core is generated for a given code, and 
 reverse-engineer
 to figure out details.

 Hope it helps.

 2015-08-24 21:59 GMT-04:00 Ömer Sinan Ağacan omeraga...@gmail.com:
 Lets say I'm running the plugin on a function with signature `Floating a 
 = a
 - a`, then the plugin has access to the `Floating` dictionary for the 
 type.
 But if I want to add two numbers together, I need the `Num` dictionary.  I
 know I should have access to `Num` since it's a superclass of `Floating`.
 How can I get access to these superclass dictionaries?

 I don't have a working code for this but this should get you started:

 let ord_dictionary :: Id = ...
 ord_class  :: Class  = ...
  in
 mkApps (Var (head (classSCSels ord_class))) [Var ord_dictionary]

 I don't know how to get Class for Ord. I do `head` here because in the case 
 of
 Ord we only have one superclass so `classSCSels` should have one Id. Then I
 apply ord_dictionary to this selector and it should return dictionary for 
 Eq.

 I assumed you already have ord_dictionary, it should be passed to your 
 function
 already if you had `(Ord a) = ` in your function.


 Now I realized you asked for getting Num from Floating. I think you should
 follow a similar path except you need two applications, first to get 
 Fractional
 from Floating and second to get Num from Fractional:

 mkApps (Var (head (classSCSels fractional_class)))
[mkApps (Var (head (classSCSels floating_class)))
[Var floating_dictionary]]

 Return value should be a Num dictionary.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: question about GHC API on GHC plugin

2015-09-04 Thread Ömer Sinan Ağacan
Type  [] (Dunno NoCPR)),JD
>> {strd = Lazy, absd = Use Many Used},0}} (Var Id{x1,anU,TyVarTy
>> TyVar{a},VanillaId,Info{0,SpecInfo []
>> ,NoUnfolding,MayHaveCafRefs,NoOneShotInfo,InlinePragma
>> {inl_src = "{-# INLINE", inl_inline = EmptyInlineSpec, inl_sat =
>> Nothing, inl_act = AlwaysActive, inl_rule =
>> FunLike},NoOccInfo,StrictSig (DmdType  [] (Dunno NoCPR)),JD
>> {strd = Lazy, absd = Use Many Used},0}})) (Var Id{x1,anU,TyVarTy
>> TyVar{a},VanillaId,Info{0,SpecInfo []
>> ,NoUnfolding,MayHaveCafRefs,NoOneShotInfo,InlinePragma
>> {inl_src = "{-# INLINE", inl_inline = EmptyInlineSpec, inl_sat =
>> Nothing, inl_act = AlwaysActive, inl_rule =
>> FunLike},NoOccInfo,StrictSig (DmdType  [] (Dunno NoCPR)),JD
>> {strd = Lazy, absd = Use Many Used},0}})
>>
>> You can find my pretty printer (and all the other code for the plugin)
>> at: 
>> https://github.com/mikeizbicki/herbie-haskell/blob/master/src/Herbie.hs#L627
>>
>> The function getDictMap
>> (https://github.com/mikeizbicki/herbie-haskell/blob/master/src/Herbie.hs#L171)
>> is where I'm constructing the dictionaries that are getting inserted
>> back into the Core.
>>
>> On Tue, Aug 25, 2015 at 7:17 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> 
>> wrote:
>>> It seems like in your App syntax you're having a non-function in function
>>> position. You can see this by looking at what failing function
>>> (splitFunTy_maybe) is doing:
>>>
>>> splitFunTy_maybe :: Type -> Maybe (Type, Type)
>>> -- ^ Attempts to extract the argument and result types from a type
>>> ... (definition is not important) ...
>>>
>>> Then it's used like this at the error site:
>>>
>>> (arg_ty, res_ty) = expectJust "cpeBody:collect_args" $
>>>splitFunTy_maybe fun_ty
>>>
>>> In your case this function is returning Nothing and then exceptJust is
>>> signalling the panic.
>>>
>>> Your code looked correct to me, I don't see any problems with that. Maybe 
>>> you're
>>> using something wrong as selectors. Could you paste CoreExpr representation 
>>> of
>>> your program?
>>>
>>> It may also be the case that the panic is caused by something else, maybe 
>>> your
>>> syntax is invalidating some assumptions/invariants in GHC but it's not
>>> immediately checked etc. Working at the Core level is frustrating at times.
>>>
>>> Can I ask what kind of plugin are you working on?
>>>
>>> (Btw, how did you generate this representation of AST? Did you write it
>>> manually? If you have a pretty-printer, would you mind sharing it?)
>>>
>>> 2015-08-25 18:50 GMT-04:00 Mike Izbicki <m...@izbicki.me>:
>>>> Thanks Ömer!
>>>>
>>>> I'm able to get dictionaries for the superclasses of a class now, but
>>>> I get an error whenever I try to get a dictionary for a
>>>> super-superclass.  Here's the Haskell expression I'm working with:
>>>>
>>>> test1 :: Floating a => a -> a
>>>> test1 x1 = x1+x1
>>>>
>>>> The original core is:
>>>>
>>>> + @ a $dNum_aJu x1 x1
>>>>
>>>> But my plugin is replacing it with the core:
>>>>
>>>> + @ a ($p1Fractional ($p1Floating $dFloating_aJq)) x1 x1
>>>>
>>>> The only difference is the way I'm getting the Num dictionary.  The
>>>> corresponding AST (annotated with variable names and types) is:
>>>>
>>>> App
>>>> (App
>>>> (App
>>>> (App
>>>> (Var +::forall a. Num a => a -> a -> a)
>>>> (Type a)
>>>> )
>>>> (App
>>>> (Var $p1Fractional::forall a. Fractional a => Num a)
>>>> (App
>>>> (Var $p1Floating::forall a. Floating a => Fractional a)
>>>> (Var $dFloating_aJq::Floating a)
>>>> )
>>>>     )
>>>> )
>>>> (Var x1::'a')
>>>> )
>>>> (Var x1::'a')
>>>>
>>>> When I insert, GHC gives the following error:
>>>>
>>>> ghc: panic! (the 'impossible' happened)
>>>>   (GHC version 7.10.1 for x86_64-unknown-linux):
>>>> expectJust cpeBo

Re: question about GHC API on GHC plugin

2015-09-04 Thread Ömer Sinan Ağacan
Typo: "You're parsing your code" I mean "You're passing your code"

2015-09-05 0:16 GMT-04:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
> Hi Mike,
>
> I'll try to hack an example for you some time tomorrow(I'm returning from ICFP
> and have some long flights ahead of me).
>
> But in the meantime, here's a working Core code, generated by GHC:
>
> f_rjH :: forall a_alz. Ord a_alz => a_alz -> Bool
> f_rjH =
>   \ (@ a_aCH) ($dOrd_aCI :: Ord a_aCH) (eta_B1 :: a_aCH) ->
> == @ a_aCH (GHC.Classes.$p1Ord @ a_aCH $dOrd_aCI) eta_B1 eta_B1
>
> You can clearly see here how Eq dictionary is selected from Ord
> dicitonary($dOrd_aCI in the example), it's just an application of selector to
> type and dictionary, that's all.
>
> This is generated from this code:
>
> {-# NOINLINE f #-}
> f :: Ord a => a -> Bool
> f x = x == x
>
> Compile it with this:
>
> ghc --make -fforce-recomp -O0 -ddump-simpl -ddump-to-file Main.hs
> -dsuppress-idinfo
>
>> Can anyone help me figure this out?  Is there any chance this is a bug in how
>> GHC parses Core?
>
> This seems unlikely, because GHC doesn't have a Core parser and there's no 
> Core
> parsing going on here, you're parsing your Code in the form of AST(CoreExpr,
> CoreProgram etc. defined in CoreSyn.hs). Did you mean something else and am I
> misunderstanding?
>
> 2015-09-04 19:39 GMT-04:00 Mike Izbicki <m...@izbicki.me>:
>> I'm still having trouble creating Core code that can extract
>> superclass dictionaries from a given dictionary.  I suspect the
>> problem is that I don't actually understand what the Core code to do
>> this is supposed to look like.  I keep getting the errors mentioned
>> above when I try what I think should work.
>>
>> Can anyone help me figure this out?  Is there any chance this is a bug
>> in how GHC parses Core?
>>
>> On Tue, Aug 25, 2015 at 9:24 PM, Mike Izbicki <m...@izbicki.me> wrote:
>>> The purpose of the plugin is to automatically improve the numerical
>>> stability of Haskell code.  It is supposed to identify numeric
>>> expressions, then use Herbie (https://github.com/uwplse/herbie) to
>>> generate a numerically stable version, then rewrite the numerically
>>> stable version back into the code.  The first two steps were really
>>> easy.  It's the last step of inserting back into the code that I'm
>>> having tons of trouble with.  Core is a lot more complicated than I
>>> thought :)
>>>
>>> I'm not sure what you mean by the CoreExpr representation?  Here's the
>>> output of the pretty printer you gave:
>>>  App (App (App (App (Var Id{+,r2T,ForAllTy TyVar{a} (FunTy (TyConApp
>>> Num [TyVarTy TyVar{a}]) (FunTy (TyVarTy TyVar{a}) (FunTy (TyVarTy
>>> TyVar{a}) (TyVarTy TyVar{a},VanillaId,Info{0,SpecInfo []
>>> ,NoUnfolding,MayHaveCafRefs,NoOneShotInfo,InlinePragma
>>> {inl_src = "{-# INLINE", inl_inline = EmptyInlineSpec, inl_sat =
>>> Nothing, inl_act = AlwaysActive, inl_rule =
>>> FunLike},NoOccInfo,StrictSig (DmdType  [] (Dunno NoCPR)),JD
>>> {strd = Lazy, absd = Use Many Used},0}}) (Type (TyVarTy TyVar{a})))
>>> (App (Var Id{$p1Fractional,rh3,ForAllTy TyVar{a} (FunTy (TyConApp
>>> Fractional [TyVarTy TyVar{a}]) (TyConApp Num [TyVarTy
>>> TyVar{a}])),ClassOpId ,Info{1,SpecInfo [BuiltinRule {ru_name =
>>> "Class op $p1Fractional", ru_fn = $p1Fractional, ru_nargs = 2, ru_try
>>> = }] ,NoUnfolding,NoCafRefs,NoOneShotInfo,InlinePragma
>>> {inl_src = "{-# INLINE", inl_inline = EmptyInlineSpec, inl_sat =
>>> Nothing, inl_act = AlwaysActive, inl_rule =
>>> FunLike},NoOccInfo,StrictSig (DmdType  [JD {strd = Str (SProd
>>> [Str HeadStr,Lazy,Lazy,Lazy]), absd = Use Many (UProd [Use Many
>>> Used,Abs,Abs,Abs])}] (Dunno NoCPR)),JD {strd = Lazy, absd = Use Many
>>> Used},0}}) (App (Var Id{$p1Floating,rh2,ForAllTy TyVar{a} (FunTy
>>> (TyConApp Floating [TyVarTy TyVar{a}]) (TyConApp Fractional [TyVarTy
>>> TyVar{a}])),ClassOpId ,Info{1,SpecInfo [BuiltinRule {ru_name =
>>> "Class op $p1Floating", ru_fn = $p1Floating, ru_nargs = 2, ru_try =
>>> }] ,NoUnfolding,NoCafRefs,NoOneShotInfo,InlinePragma
>>> {inl_src = "{-# INLINE", inl_inline = EmptyInlineSpec, inl_sat =
>>> Nothing, inl_act = AlwaysActive, inl_rule =
>>> FunLike},NoOccInfo,StrictSig (DmdType  [JD {strd = Str (SProd
>>> [Str 
>>> HeadStr,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy,Lazy]),

Re: [GHC] #10487: DeriveGeneric breaks when the same data name is used in different modules

2015-09-24 Thread Ömer Sinan Ağacan
Done.

It's be the best if we could add a test case that uses multiple
packages, but as far as I could see current test runner isn't
supporting this setup.

2015-09-24 12:17 GMT-04:00 Simon Peyton Jones :
> Can someone fill in the regression-test test-case on the ticket?   I assume 
> there is one??
>
> Simon
>
> | -Original Message-
> | From: ghc-tickets [mailto:ghc-tickets-boun...@haskell.org] On Behalf Of
> | GHC
> | Sent: 24 September 2015 08:51
> | Cc: ghc-tick...@haskell.org
> | Subject: Re: [GHC] #10487: DeriveGeneric breaks when the same data name is
> | used in different modules
> |
> | #10487: DeriveGeneric breaks when the same data name is used in different
> | modules
> | -+
> | -
> | Reporter:  andreas.abel  |   Owner:  osa1
> | Type:  bug   |  Status:  closed
> | Priority:  highest   |   Milestone:  8.0.1
> |Component:  Compiler  | Version:  7.10.1
> |   Resolution:  fixed |Keywords:
> | Operating System:  Unknown/Multiple  |Architecture:
> |  |  Unknown/Multiple
> |  Type of failure:  None/Unknown  |   Test Case:
> |   Blocked By:|Blocking:
> |  Related Tickets:|  Differential Revisions:
> | Phab:D1081
> | -+
> | -
> | Changes (by ezyang):
> |
> |  * status:  new => closed
> |  * resolution:   => fixed
> |
> |
> | Comment:
> |
> |  Pushed. I assume we aren't backporting to 7.10?
> |
> | --
> | Ticket URL:
> |  | ll.org%2ftrac%2fghc%2fticket%2f10487%23comment%3a19=01%7c01%7csimonpj
> | %40064d.mgd.microsoft.com%7c82714a5e33ae4f38b09908d2c4b539d7%7c72f988bf86f
> | 141af91ab2d7cd011db47%7c1=CtjXUTaEpVHihCDcvgifJ%2fTSw30niJxDDFsFqE3m
> | ykY%3d>
> | GHC
> |  | ll.org%2fghc%2f=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c82714a5e
> | 33ae4f38b09908d2c4b539d7%7c72f988bf86f141af91ab2d7cd011db47%7c1=76x0
> | GO1GY8YfHiI7vNNS7U%2b9XTkUVU72nnq76N4V87o%3d>
> | The Glasgow Haskell Compiler
> | ___
> | ghc-tickets mailing list
> | ghc-tick...@haskell.org
> | https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haske
> | ll.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
> | tickets=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c82714a5e33ae4f38
> | b09908d2c4b539d7%7c72f988bf86f141af91ab2d7cd011db47%7c1=Y08eOOpKx37o
> | TYsnGW2m1pvQGW31Ssq%2fwwBPAwt3nUo%3d
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: question about coercions between primitive types in STG level

2015-12-07 Thread Ömer Sinan Ağacan
Thanks Simon, primops worked fine, but not I'm getting assembler errors(even
though -dcore-lint, -dstg-lint and -dcmm-lint are all passing).

The error is caused by this STG expression:

case (#,#) [ds_gX8 ds_gX9] of _ {
  (#,#) tag_gWR ubx_gWS ->
  case tag_gWR of tag_gWR {
__DEFAULT -> GHC.Err.undefined;
1# ->
let {
  sat_sWD :: [GHC.Types.Char] =
  \u srt:SRT:[roK :-> GHC.Show.$fShowInt] []
  let { sat_sWC :: GHC.Types.Int = NO_CCS
GHC.Types.I#! [ubx_gWS];
  } in  GHC.Show.show GHC.Show.$fShowInt sat_sWC; } in
let {
  sat_sWB :: [GHC.Types.Char] =
  \u srt:SRT:[0k :-> GHC.CString.unpackCString#] []
  GHC.CString.unpackCString# "Left "#;
} in  GHC.Base.++ sat_sWB sat_sWD;
2# ->
let {
  co_gWT :: GHC.Prim.Float# =
  sat-only \s [] int2Float# [ubx_gWS]; } in
let {
  sat_sWH :: [GHC.Types.Char] =
  \u srt:SRT:[rd2 :-> GHC.Float.$fShowFloat] []
  let { sat_sWG :: GHC.Types.Float = NO_CCS
GHC.Types.F#! [co_gWT];
  } in  GHC.Show.show GHC.Float.$fShowFloat
sat_sWG; } in
let {
  sat_sWF :: [GHC.Types.Char] =
  \u srt:SRT:[0k :-> GHC.CString.unpackCString#] []
  GHC.CString.unpackCString# "Right "#;
} in  GHC.Base.++ sat_sWF sat_sWH;
  };
};

In the first case(when the tag is 1#) I'm not doing any coercions, second
argument of the tuple is directly used. In the second case(when the tag is 2#),
I'm generating this let-binding:

let {
  co_gWT :: GHC.Prim.Float# =
  sat-only \s [] int2Float# [ubx_gWS]; }

And then in the RHS of case alternative I'm using co_gWT instead of ubx_gWS,
but for some reason GHC is generating invalid assembly for this expression:

/tmp/ghc2889_0/ghc_2.s: Assembler messages:

/tmp/ghc2889_0/ghc_2.s:125:0: error:
 Error: `16(%xmm1)' is not a valid base/index expression
`gcc' failed in phase `Assembler'. (Exit code: 1)

The assembly seems to be:

 Asm code 
.section .text
.align 8
.quad 4294967296
.quad 18
co_gWT_info:
_cY7:
_cY9:
movq 16(%xmm1),%rax
cvtsi2ssq %rax,%xmm0
movss %xmm0,%xmm1
jmp *(%rbp)
.size co_gWT_info, .-co_gWT_info

Do you have any ideas why this may be happening?

2015-12-07 7:23 GMT-05:00 Simon Peyton Jones :
> If memory serves, there are primops for converting between unboxed values of 
> different widths.
>
> Certainly converting between a float and a non-float will require an 
> instruction on some architectures, since they use different register sets.
>
> Re (2) I have no idea.  You'll need to get more information... pprTrace or 
> something.
>
> Simon
>
> |  -Original Message-
> |  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ömer
> |  Sinan Agacan
> |  Sent: 06 December 2015 18:25
> |  To: ghc-devs 
> |  Subject: question about coercions between primitive types in STG level
> |
> |  Hi all,
> |
> |  In my compiler pass(D1559, see ElimUbxSums.hs) I'm doing some unsafe
> |  coercions at the STG level. It works fine for lifted types, but for
> |  unlifted ones I'm having some problems. What I'm trying to do is given
> |  a number of primitive types I'm finding the one with biggest size, and
> |  then generating a constructor that takes this biggest primitive type
> |  as argument.
> |
> |  The problem is that this is not working very well - GHC is generating
> |  illegal instructions that try to load a F32 value to a register
> |  allocated for I64, using movss instruction.
> |
> |  CoreLint is catching this error and printing this:
> |
> |  Cmm lint error:
> |in basic block c1hF
> |  in assignment:
> |_g16W::I64 = 4.5 :: W32;   // CmmAssign
> |Reg ty: I64
> |Rhs ty: F32
> |
> |  So I have two questions about this:
> |
> |  1. Is there a way to safely do this? What are my options here? What
> |  I'm trying
> | to do is to use a single data constructor field for different
> |  primitive
> | types.  The field is guaranteed to be as big as necessary.
> |
> |  2. In the Cmm code shown above, the type annotation is showing `W32`
> |  but in the
> | error message it says `F32`. I'm confused about this, is this error
> |  message
> | given because the sizes don't match? (64bits vs 32bits) Why the
> |  type
> | annotation says W32 while the value has type F32?
> |
> |  Thanks..
> |  ___
> |  ghc-devs mailing list
> |  ghc-devs@haskell.org
> |  

Re: Does the Strict extension make monadic bindings strict?

2015-12-08 Thread Ömer Sinan Ağacan
I think this is a problem/bug in the implementation. In the "function
definitions" section of the wiki page it says the argument will have a
bang pattern. But then this code:

do x <- ...
   return (x + 1)

which is just a syntactic sugar for `... >>= \x -> return (x + 1)`
doesn't have the bang pattern in `x`.

(See also a related email I sent to ghc-devs yesterday:
https://mail.haskell.org/pipermail/ghc-devs/2015-December/010699.html)

2015-12-08 12:27 GMT-05:00 David Kraeutmann :
> While there's a fundamental difference between (>>=) and let-bindings, it
> might be worth adding to the docs that -XStrict only makes let bindings
> strict.
>
>
> On 12/08/2015 06:22 PM, Rob Stewart wrote:
>
> Are the following two programs equivalent with respect to the strictness
> of `readFile`?
>
> --8<---cut here---start->8---
> {-# LANGUAGE BangPatterns #-}
>
> module Main where
>
> main = do
>   !contents <- readFile "foo.txt"
>   print contents
> --8<---cut here---end--->8---
>
> And:
>
> --8<---cut here---start->8---
> {-# LANGAUGE Strict #-}
>
> module Main where
>
> main = do
>   contents <- readFile "foo.txt"
>   print contents
> --8<---cut here---end--->8---
>
> The documentation on "Strict-by-default pattern bindings" gives
> let/where binding as an example, but there is not a monadic bind example.
> http://downloads.haskell.org/~ghc/master/users-guide/glasgow_exts.html#strict-by-default-pattern-bindings
>
> Inspecting GHC Core for these two programs suggests that
>
> !contents <- readFile "foo.txt"
>
> is not equivalent to (with Strict enabled):
>
> contents <- readFile "foo.txt"
>
> Here's core using BangPatterns:
>
> (readFile (unpackCString# "foo.txt"#))
> (\ (contents_asg :: String) ->
>case contents_asg of contents1_Xsk { __DEFAULT ->
>print @ String $dShow_rYy contents1_Xsk
>})
>
> Here's core using Strict:
>
> (readFile (unpackCString# "foo.txt"#))
> (\ (contents_asg :: String) ->
>print @ String $dShow_rYv contents_asg)
>
> Does this core align with the design of the Strict extension?
>
> If it does, are users going to understand that using Strict is going to
> make let/where bindings strict, but is not going to make <- or >>=
> bindings strict?
>
> --
> Rob Stewart
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Another question about -XStrict: Why not implement it as a Core pass?

2015-12-08 Thread Ömer Sinan Ağacan
So this is another question comes to mind. It seems to me like it
would be a lot easier to implement, we could even implement it as a
plugin, without changing anything in GHC. (I mean -XStrict, not
-XStrictData)

I'm wondering why it's currently implemented on Haskell syntax. Any
ideas? Is it because of some typechecking related things?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


question about coercions between primitive types in STG level

2015-12-06 Thread Ömer Sinan Ağacan
Hi all,

In my compiler pass(D1559, see ElimUbxSums.hs) I'm doing some unsafe coercions
at the STG level. It works fine for lifted types, but for unlifted ones I'm
having some problems. What I'm trying to do is given a number of primitive
types I'm finding the one with biggest size, and then generating a constructor
that takes this biggest primitive type as argument.

The problem is that this is not working very well - GHC is generating illegal
instructions that try to load a F32 value to a register allocated for I64,
using movss instruction.

CoreLint is catching this error and printing this:

Cmm lint error:
  in basic block c1hF
in assignment:
  _g16W::I64 = 4.5 :: W32;   // CmmAssign
  Reg ty: I64
  Rhs ty: F32

So I have two questions about this:

1. Is there a way to safely do this? What are my options here? What I'm trying
   to do is to use a single data constructor field for different primitive
   types.  The field is guaranteed to be as big as necessary.

2. In the Cmm code shown above, the type annotation is showing `W32` but in the
   error message it says `F32`. I'm confused about this, is this error message
   given because the sizes don't match? (64bits vs 32bits) Why the type
   annotation says W32 while the value has type F32?

Thanks..
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Plugins: Accessing unexported bindings

2015-12-06 Thread Ömer Sinan Ağacan
2015-12-06 2:01 GMT-05:00 Levent Erkok :
> The mg_binds field of the ModGuts seem to only contain the bindings that are
> exported from the module being compiled.

This is not true, it contains all the definitions in the module and I'm relying
on this all the time. I just tested again and it definitely has all the
definitions in the module, exported or not.

If it doesn't export everything in the module some optimizers couldn't really
work. At least in my case the plugin API would be basically useless.

May I ask how are you testing this?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Kinds of type synonym arguments

2015-12-06 Thread Ömer Sinan Ağacan
In this program:

{-# LANGUAGE MagicHash, UnboxedTuples #-}

module Main where

import GHC.Prim
import GHC.Types

type Tuple a b = (# a, b #)

main = do
  let -- x :: Tuple Int# Float#
  x :: (# Int#, Float# #)
  x = (# 1#, 0.0# #)

  return ()

If I use the first type declaration for 'x' I'm getting this error message:

Expecting a lifted type, but ‘Int#’ is unlifted

Indeed, if I look at the kinds of arguments of 'Tuple':

λ:7> :k Tuple
Tuple :: * -> * -> #

It's star. I was wondering why is this not 'OpenKind'(or whatever the
super-kind of star and hash). Is there a problem with this? Is this a bug?
Or is this simply because type synonyms are implemented before OpenKinds?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: ok to do reformatting commits?

2015-12-02 Thread Ömer Sinan Ağacan
2015-11-24 22:14 GMT-05:00 Evan Laforge :
> When I was doing a recent patch, I was annoyed by lint errors about
>>80 lines when I was just conforming to the existing style.

I just wanted to mention that I've been using --nolint flag of arc diff lately
and it's really great. It doesn't clutter Phabricator diff page with hundreds
of "lint error" boxes, unlike plain `arc diff`.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


-XStrict: Why some binders are not made strict?

2015-12-07 Thread Ömer Sinan Ağacan
Let's say I have this code:

zip :: [a] -> [b] -> [(a, b)]
zip [] [] = []
zip (x : xs) (y : ys) = (x, y) : zip xs ys

With -XStrict 'x', 'xs', 'y' and 'ys' don't become strict. I'm wondering about
the motivation behind this, I found this interesting. I always thought -XStrict
gives me this guarantee: If I'm using an already-defined variable(bound by a
let or pattern matching) in an expression, I can be sure that the variable
won't be bottom in that expression, because it would be `seq`d before the
expression is evaluated.

So if I have

case ... of
D x y -> 

or

let x = ...
y = ...
 in 

In both cases I was thinking that in  'x' and 'y' can't be bottom(with
-XStrict). This would make -XStrict programs evaluate like they would in a
call-by-value language(even though in the RTS level thunks will be built).
Variables can't range over computations; all binders evaluated strictly etc.

Can anyone tell me about the motivation behind this decision?

I think the wiki page actually conflicts with itself. It says "...
bindings to be
strict by default" but then in "case expressions" sections says

case x of (a,b) -> rhs

is interpreted as

case x of !(a,b) -> rhs

Here bindings 'a' and 'b' are not made strict. I'd expect something like:

case x of (!a,!b) -> rhs

(Which seems to be invalid Haskell, but same effect could be achieved with `seq
a (seq b rhs)`)

Thanks..

(I also realized that the wiki page doesn't mention bindings in do syntax, is
it because this case is implied by "function definitions"? That is, bangs are
added after do syntax is desugared and so they become strict?)
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: -XStrict: Why some binders are not made strict?

2015-12-07 Thread Ömer Sinan Ağacan
> Aren't those already guaranteed to be strict because of pattern matching? Try
> it again with irrefutable patterns.

But pattern matching only forces the evaluation up to the pattern that is
matched. We need another pattern matching(or seq etc.) on x, y, xs and ys here.
If you look at the generated Core you'll see it more clearly I think(you'll see
that no pattern matching on x y xs and ys are done in Core).

2015-12-07 20:43 GMT-05:00 Brandon Allbery <allber...@gmail.com>:
> On Mon, Dec 7, 2015 at 8:40 PM, Ömer Sinan Ağacan <omeraga...@gmail.com>
> wrote:
>>
>> With -XStrict 'x', 'xs', 'y' and 'ys' don't become strict. I'm wondering
>> about
>> the motivation behind this, I found this interesting. I always thought
>> -XStrict
>> gives me this guarantee: If I'm using an already-defined variable(bound by
>> a
>> let or pattern matching) in an expression, I can be sure that the variable
>> won't be bottom in that expression, because it would be `seq`d before the
>> expression is evaluated.
>
>
> Aren't those already guaranteed to be strict because of pattern matching?
> Try it again with irrefutable patterns.
>
> --
> brandon s allbery kf8nh   sine nomine associates
> allber...@gmail.com  ballb...@sinenomine.net
> unix, openafs, kerberos, infrastructure, xmonadhttp://sinenomine.net
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: question about coercions between primitive types in STG level

2015-12-09 Thread Ömer Sinan Ağacan
Thanks for all the answers,

Simon, do you remember anything about the ticket about converting between
floating point types and integers? I spend quite a bit of time in Trac
searching for this but couldn't find it.


Before implementing a new primop, MachOp, and code generation functions for
that I tried this: Since type signature of this new primop will be same as
float2Int# I thought maybe I should first make current implementation working,
and then I can just change the primop to coerceFloat2Int# and it would work.

However I'm still this same problem(illegal assembly). What I changed is I
looked at the GHC-generated, working STG code that uses float2Int#, and tried
to generate a very similar code myself. The change I had to make for this was
to use a case expression instead of let expression to bind result of this
primop.

Here's an example. This STG is working fine:

sat_s1Ic :: GHC.Types.Float -> GHC.Types.IO () =
\r srt:SRT:[0B :-> System.IO.print,
rUB :-> GHC.Show.$fShowInt] [ds_s1I7]
case
ds_s1I7 :: GHC.Types.Float :: Alg GHC.Types.Float
of
(wild_s1I8 :: GHC.Types.Float)
{ GHC.Types.F# (f_s1I9 :: GHC.Prim.Float#) ->
  case
  float2Int# [(f_s1I9 :: GHC.Prim.Float#)] :: Prim
GHC.Prim.Int#
  of
  (sat_s1Ia :: GHC.Prim.Int#)
  { __DEFAULT ->
let {
  sat_s1Ib :: GHC.Types.Int =
  NO_CCS GHC.Types.I#! [(sat_s1Ia ::
GHC.Prim.Int#)];
} in
  System.IO.print
:: forall a_aUq. GHC.Show.Show a_aUq =>
a_aUq -> GHC.Types.IO ()
  (GHC.Show.$fShowInt :: GHC.Show.Show
GHC.Types.Int)
  (sat_s1Ib :: GHC.Types.Int);
  };
};

(Sorry for extra noisy output, I changed Outputable instances to print some
extra info)

This code is generated by GHC for a program that uses the primop directly and
it's working. This is the code generated by my pass:

Main.main2 :: [GHC.Types.Char] =
\u srt:SRT:[r4 :-> Main.showEither2] []
case
case
float2Int# [1.2#] :: Prim GHC.Prim.Int#
of
(co_g21m :: GHC.Prim.Int#)
{ __DEFAULT -> (#,#) [2## (co_g21m :: GHC.Prim.Int#)];
} :: UbxTup 2
of
(sat_s21b :: (# GHC.Prim.Int#, GHC.Prim.Int# #))
{ (#,#) (sat_g21R :: GHC.Prim.Int#) (sat_g21S :: GHC.Prim.Int#) ->
  Main.showEither2
:: (# GHC.Prim.Int#, GHC.Prim.Int# #) -> [GHC.Types.Char]
  (sat_g21R :: GHC.Prim.Int#) (sat_g21S :: GHC.Prim.Int#);
};

Types look correct, and I'm using a case expression to bind the result of the
primop. But generated assembly for this is still invalid! I'm wondering if
there are some invariants that I'm invalidating here, even although -dstg-lint
is passing. Does anyone know what I might be doing wrong here?

One thing that I'm not being very careful is the information about live
variables, but I don't see how it might be related with this illegal
instruction error.

Thanks again..

2015-12-07 13:57 GMT-05:00 Simon Marlow :
> Simon's right, you need an explicit conversion, and unfortunately those
> conversions don't currently exist.  You would have to add them to the MachOp
> type, and implement them in each of the native code generators.
>
> The good news is that if you did this, we could implement cheap conversions
> between the IEEE floating point types and their representations as unboxed
> integers, which is currently done by poking the values to memory and then
> peeking them back at the desired type. There's a ticket for this around
> somewhere
>
> Cheers
> Simon
>
>
> On 07/12/2015 12:23, Simon Peyton Jones wrote:
>>
>> If memory serves, there are primops for converting between unboxed values
>> of different widths.
>>
>> Certainly converting between a float and a non-float will require an
>> instruction on some architectures, since they use different register sets.
>>
>> Re (2) I have no idea.  You'll need to get more information... pprTrace or
>> something.
>>
>> Simon
>>
>> |  -Original Message-
>> |  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ömer
>> |  Sinan Agacan
>> |  Sent: 06 December 2015 18:25
>> |  To: ghc-devs 
>> |  Subject: question about coercions between primitive types in STG level
>> |
>> |  Hi all,
>> |
>> |  In my compiler pass(D1559, see ElimUbxSums.hs) I'm doing some unsafe
>> |  coercions at the STG level. It works fine for lifted types, but for
>> |  unlifted ones I'm having some problems. What I'm trying to do is given
>> |  a number of primitive types I'm finding the one with 

Re: -XStrict: Why some binders are not made strict?

2015-12-11 Thread Ömer Sinan Ağacan
I agree with Roman here.

Probably another reason for making every binding strict is this: (sorry if this
is mentioned)

Suppose I imported `data D = D ...` from another library and I'm in -XStrict.
In this code:

case ... of
  D b1 b2 ... -> 

I should be able to assume that b1, b2 ... etc. are all strict(that is, WHNF in
) becuase I'm in -XStrict. This also makes the behavior more consistent,
I think.

2015-12-11 7:57 GMT-05:00 Roman Cheplyaka :
> On 12/11/2015 02:21 PM, Johan Tibell wrote:
>> If we force strictness all the way down it's not really call-by-value
>> either, because the caller doesn't know what to evaluate (I think).
>
> Not sure what you mean here.
>
>> In addition, making pattern matching strict in this way makes it hard to
>> mix and match strict and lazy data types (e.g. Maybe), because using a
>> lazy data type from another module will make it appear strict in your
>> code (hurting modularity).
>
> I don't think this is a case about modularity. A lazy Maybe value
> defined in a lazy module remains lazy; and you can pass it to lazy
> functions without forcing it. Only when you pattern match on it *in the
> strict module*, the evaluation happens.
>
> As I said, I prefer this semantics mainly because it's easier to
> explain: all variables (and underscores) bound in a strict module refer
> to WHNF values. Do you have a similarly simple explanation for the
> semantics you're suggesting?
>
> Roman
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Kinds of type synonym arguments

2015-12-16 Thread Ömer Sinan Ağacan
I understand the problem, but I was actually talking about something else. We
already have some other restrictions for polymorphism over boxed and unboxed
types. For example:

data T a b = T a b

This has kind * -> * -> *. Similarly, kinds of 'a' and 'b' in this function are
*:

f :: (a, b) -> a
f (x, _) = x

I'm not trying to make this function polymorphic over both hash and start
types. I'm just trying to make something like this possible:

f :: (Int#, b) -> b
f (_, b) = b

Here the polymorphic part is boxed, * type. This should not be that hard, I
think. Unless on-demand code generation part as mentioned by Dan is too much
work.

In any case, this is not that big deal. When I read the code I thought this
should be a trivial change but apparently it's not.

2015-12-15 23:44 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
> Yes. I completely agree with Dan.
>
> I wasn't suggesting that boxed tuples would be able to work with unboxed 
> arguments. I was just suggesting that it should be possible to declare a 
> levity-polymorphic type synonym for unboxed tuples, if that's what you need.
>
> Richard
>
> On Dec 15, 2015, at 10:04 PM, Dan Doel <dan.d...@gmail.com> wrote:
>
>> This is not a simple change at all, though.
>>
>> The reason that (,) cannot accept arguments of kind # is not just that
>> there was no levity abstraction. You simply cannot abstract over # in
>> the same way as you can *, because the types in # are not represented
>> uniformly. Creating a tuple with an argument of kind # would require
>> generating code for (at the least) each different size of thing that
>> can go in #; but there are infinitely many of those, because of
>> unboxed tuples, so  you probably have to do on-demand code generation
>> when particular types are used.
>>
>> And of course, the evaluation conventions change between # and *, so
>> you have to deal with that if tuples are supposed to accept types of
>> both kinds. See the stuff at:
>>
>>https://ghc.haskell.org/trac/ghc/wiki/UnliftedDataTypes
>>
>> for instance. Note that that that page is only considering being able
>> to abstract over the portion of # that is represented uniformly by a
>> pointer, though. Things like Int#, Double# and (# Int#, Double #) are
>> completely out of its scope.
>>
>> This isn't just the typing on (,) being overly restrictive. It would
>> be a pretty fundamental change that would, I assume, be non-trivial to
>> implement. I think it would be non-trivial to come up with a good
>> design, too, really.
>>
>> -- Dan
>>
>>
>> On Tue, Dec 15, 2015 at 6:25 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> 
>> wrote:
>>> Oh sorry, I just mean that currently boxed tuples don't accept unboxed 
>>> types:
>>>
>>>λ> :k ( Int#, Int )
>>>
>>>:1:3: error:
>>>• Expecting a lifted type, but ‘Int#’ is unlifted
>>>• In the type ‘(Int#, Int)’
>>>
>>> But unboxed variant of exactly the same thing is accepted:
>>>
>>>λ> :k (# Int#, Int #)
>>>(# Int#, Int #) :: #
>>>
>>> I was hoping make these two the same by adding levity arguments and making 
>>> type
>>> arguments depend on levity arguments, just like how unboxed tuple types are
>>> implemented (as described in Note [Unboxed tuple levity vars]).
>>>
>>> The changes in tuple DataCon and TyCon generation is fairly simple (in fact 
>>> I
>>> just implemented that part) but the rest of the compiler started panicking. 
>>> So
>>> my question is, is there a reason for not doing this, because otherwise I'd
>>> like to fix panics etc. and make this change.
>>>
>>> 2015-12-15 18:08 GMT-05:00 Simon Peyton Jones <simo...@microsoft.com>:
>>>> What is "this" that you propose to implement?  Is there a wiki page that 
>>>> describes the design?
>>>>
>>>> Simon
>>>>
>>>> | -Original Message-
>>>> | From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ömer 
>>>> Sinan
>>>> | Agacan
>>>> | Sent: 15 December 2015 23:06
>>>> | To: Richard Eisenberg <e...@cis.upenn.edu>
>>>> | Cc: ghc-devs <ghc-devs@haskell.org>
>>>> | Subject: Re: Kinds of type synonym arguments
>>>> |
>>>> | Hi Richard,
>>>> |
>>>> | Now that we have levity arguments I'm wondering if we should go ahead and
>>>> | implement this. The code is already ther

Re: Kinds of type synonym arguments

2015-12-15 Thread Ömer Sinan Ağacan
Hi Richard,

Now that we have levity arguments I'm wondering if we should go ahead and
implement this. The code is already there - unboxed tuples have levity
arguments and then type arguments depend on the levity arguments, so this
works:

λ> :k (# Int, Int# #)
(# Int, Int# #) :: #

But this doesn't because boxed tuples are not implemented that way:

λ> :k ( Int, Int# )

:1:8: error:
• Expecting a lifted type, but ‘Int#’ is unlifted
• In the type ‘(Int, Int#)’

The implementation looked fairly simple so I just tried to lift this
restriction (I basically merged the code that generates TyCons and DataCons for
unboxed and boxed tuples in WiredInTys), but some other parts of the compiler
started to panic. Should I investigate this further or are there any problems
with this that we need to solve first?

If there's a problem with this I think we should at least add a NOTE in
TysWiredIn. Note [Unboxed tuple levity vars] explains how levity vars are used
in unboxed tuples, but there's no comments or notes about why we don't do the
same for boxed tuples.

Also, I was wondering if OpenKind is deprecated now. Can I assume that levity
arguments do that work now and we no longer need OpenKind?

Thanks

2015-12-06 21:45 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
> I think this is a consequence of the rule that we never abstract over types 
> of kind #. But I believe this should work with my branch:
>
>> type Tuple (a :: TYPE v1) (b :: TYPE v2) = (# a, b #)
>
> The user would have to request that the synonym be used over both * and #, 
> but the synonym should work. The need to request the special treatment might 
> be lifted, but we'd have to think hard about where we want the generality by 
> default and where we want simpler behavior by default.
>
> Richard
>
> On Dec 6, 2015, at 1:55 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:
>
>> In this program:
>>
>>{-# LANGUAGE MagicHash, UnboxedTuples #-}
>>
>>module Main where
>>
>>import GHC.Prim
>>import GHC.Types
>>
>>type Tuple a b = (# a, b #)
>>
>>main = do
>>  let -- x :: Tuple Int# Float#
>>  x :: (# Int#, Float# #)
>>  x = (# 1#, 0.0# #)
>>
>>  return ()
>>
>> If I use the first type declaration for 'x' I'm getting this error message:
>>
>>Expecting a lifted type, but ‘Int#’ is unlifted
>>
>> Indeed, if I look at the kinds of arguments of 'Tuple':
>>
>>λ:7> :k Tuple
>>Tuple :: * -> * -> #
>>
>> It's star. I was wondering why is this not 'OpenKind'(or whatever the
>> super-kind of star and hash). Is there a problem with this? Is this a bug?
>> Or is this simply because type synonyms are implemented before OpenKinds?
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Kinds of type synonym arguments

2015-12-15 Thread Ömer Sinan Ağacan
Oh sorry, I just mean that currently boxed tuples don't accept unboxed types:

λ> :k ( Int#, Int )

:1:3: error:
• Expecting a lifted type, but ‘Int#’ is unlifted
• In the type ‘(Int#, Int)’

But unboxed variant of exactly the same thing is accepted:

λ> :k (# Int#, Int #)
(# Int#, Int #) :: #

I was hoping make these two the same by adding levity arguments and making type
arguments depend on levity arguments, just like how unboxed tuple types are
implemented (as described in Note [Unboxed tuple levity vars]).

The changes in tuple DataCon and TyCon generation is fairly simple (in fact I
just implemented that part) but the rest of the compiler started panicking. So
my question is, is there a reason for not doing this, because otherwise I'd
like to fix panics etc. and make this change.

2015-12-15 18:08 GMT-05:00 Simon Peyton Jones <simo...@microsoft.com>:
> What is "this" that you propose to implement?  Is there a wiki page that 
> describes the design?
>
> Simon
>
> | -Original Message-
> | From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ömer Sinan
> | Agacan
> | Sent: 15 December 2015 23:06
> | To: Richard Eisenberg <e...@cis.upenn.edu>
> | Cc: ghc-devs <ghc-devs@haskell.org>
> | Subject: Re: Kinds of type synonym arguments
> |
> | Hi Richard,
> |
> | Now that we have levity arguments I'm wondering if we should go ahead and
> | implement this. The code is already there - unboxed tuples have levity
> | arguments and then type arguments depend on the levity arguments, so this
> | works:
> |
> | λ> :k (# Int, Int# #)
> | (# Int, Int# #) :: #
> |
> | But this doesn't because boxed tuples are not implemented that way:
> |
> | λ> :k ( Int, Int# )
> |
> | :1:8: error:
> | • Expecting a lifted type, but ‘Int#’ is unlifted
> | • In the type ‘(Int, Int#)’
> |
> | The implementation looked fairly simple so I just tried to lift this
> | restriction (I basically merged the code that generates TyCons and DataCons
> | for
> | unboxed and boxed tuples in WiredInTys), but some other parts of the 
> compiler
> | started to panic. Should I investigate this further or are there any 
> problems
> | with this that we need to solve first?
> |
> | If there's a problem with this I think we should at least add a NOTE in
> | TysWiredIn. Note [Unboxed tuple levity vars] explains how levity vars are
> | used
> | in unboxed tuples, but there's no comments or notes about why we don't do 
> the
> | same for boxed tuples.
> |
> | Also, I was wondering if OpenKind is deprecated now. Can I assume that 
> levity
> | arguments do that work now and we no longer need OpenKind?
> |
> | Thanks
> |
> | 2015-12-06 21:45 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
> | > I think this is a consequence of the rule that we never abstract over 
> types
> | of kind #. But I believe this should work with my branch:
> | >
> | >> type Tuple (a :: TYPE v1) (b :: TYPE v2) = (# a, b #)
> | >
> | > The user would have to request that the synonym be used over both * and #,
> | but the synonym should work. The need to request the special treatment might
> | be lifted, but we'd have to think hard about where we want the generality by
> | default and where we want simpler behavior by default.
> | >
> | > Richard
> | >
> | > On Dec 6, 2015, at 1:55 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> 
> wrote:
> | >
> | >> In this program:
> | >>
> | >>{-# LANGUAGE MagicHash, UnboxedTuples #-}
> | >>
> | >>module Main where
> | >>
> | >>import GHC.Prim
> | >>import GHC.Types
> | >>
> | >>type Tuple a b = (# a, b #)
> | >>
> | >>main = do
> | >>  let -- x :: Tuple Int# Float#
> | >>  x :: (# Int#, Float# #)
> | >>  x = (# 1#, 0.0# #)
> | >>
> | >>  return ()
> | >>
> | >> If I use the first type declaration for 'x' I'm getting this error
> | message:
> | >>
> | >>Expecting a lifted type, but ‘Int#’ is unlifted
> | >>
> | >> Indeed, if I look at the kinds of arguments of 'Tuple':
> | >>
> | >>λ:7> :k Tuple
> | >>Tuple :: * -> * -> #
> | >>
> | >> It's star. I was wondering why is this not 'OpenKind'(or whatever the
> | >> super-kind of star and hash). Is there a problem with this? Is this a 
> bug?
> | >> Or is this simply because type synonyms are implemented before OpenKinds?
> | >> ___
> | &g

Re: Implementation idea for unboxed polymorphic types

2016-01-05 Thread Ömer Sinan Ağacan
That's a really good question, I think. I tried to make it working here:
https://gist.github.com/osa1/00597c24a79816c7ef90/

In that code, just assume whenever you see a type or constructor with Ubx
prefix it's just magically get unboxed.

I added lots of inline comments about problems and results etc. but in short,
we have a problem that this idea doesn't solve: GHC doesn't generate
specialized functions at all. So if I have a function that's too big to inline
or if I simply don't want to inline for some reason, we're out of luck.

(I don't understand this restriction, specialization without inlining would be
very useful in lots of cases, I think)

Second thing is ideally we shouldn't be using unboxed types in the code
manually. For example, in the `distance` functions we should really write
`distance :: Point a => Point a -> a`. But this means that `Unbox` typeclass
needs to be magical, GHC should recognize it and specialize functions using
Unbox dictionaries.

2015-11-17 10:54 GMT-05:00 Alexey Vagarenko <vagare...@gmail.com>:
> At the moment, GHC does not support type families over kind #,
> but if it did, would this code do the trick
> https://gist.github.com/vagarenko/077c6dd73cd610269aa9 ?
>
> 2015-11-16 22:32 GMT+05:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
>>
>> > But I don't see why you'd need quoting at constructor calls. Couldn't
>> > you
>> > just have a type class like `PointFamily`?
>>
>> This is exactly right, my memory has failed me. My initial implementation
>> didn't use the type family trick, I had further attempts that use type
>> families
>> but honestly I don't remember how good it worked. This was quite a while
>> ago.
>>
>> 2015-11-15 19:41 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
>> > After reading Francesco's original post, I immediately thought of Ömer's
>> > proposed approach, of using Template Haskell to produce the right data
>> > family instances. But I don't see why you'd need quoting at constructor
>> > calls. Couldn't you just have a type class like `PointFamily`? I'd be more
>> > interested to see client code in Ömer's version than the TH generation 
>> > code.
>> >
>> > The TH approach would seem to require having a fixed set of
>> > specializations, which is a downside. But I'm not sure it's so much of a
>> > downside that the approach is unusable.
>> >
>> > Richard
>> >
>> > On Nov 15, 2015, at 10:08 AM, Ömer Sinan Ağacan <omeraga...@gmail.com>
>> > wrote:
>> >
>> >> I had started working on exactly the same thing at some point. I had a
>> >> TemplateHaskell-based implementation which _almost_ worked.
>> >>
>> >> The problem was that the syntax was very, very heavy. Because I had to
>> >> use
>> >> quotes for _every_ constructor application(with explicitly passed
>> >> types).
>> >> (because I had a specialized constructor for every instantiation of
>> >> this
>> >> generic type)
>> >>
>> >> Another problem was that because of how TemplateHaskell quotes
>> >> evaluated, I
>> >> couldn't use a `List Int` where `List` is a template without first
>> >> manually
>> >> adding a line for generating specialized version of `List` on `Int`.
>> >>
>> >> When all of these combined it became very hard to use. But it was a
>> >> proof-of-concept and I think it worked.
>> >>
>> >> (Code is horrible so I won't share it here :) I had to maintain a state
>> >> shared
>> >> with different TH quote evaluations etc.)
>> >>
>> >> 2015-11-15 5:26 GMT-05:00 Francesco Mazzoli <f...@mazzo.li>:
>> >>> (A nicely rendered version of this email can be found at
>> >>> <https://gist.github.com/bitonic/52cfe54a2dcdbee1b7f3>)
>> >>>
>> >>> ## Macro types
>> >>>
>> >>> I very often find myself wanting unboxed polymorphic types
>> >>> (e.g. types that contain `UNPACK`ed type variables). I find
>> >>> it extremely frustrating that it's easier to write fast _and_
>> >>> generic code in C++ than in Haskell.
>> >>>
>> >>> I'd like to submit to the mailing list a very rough proposal
>> >>> on how this could be achieved in a pretty straightforward way
>> >>> in GHC.
>> >>>
>> >>> The proposal is meant to be a proof of concept, just to show that
>> >>> this could be done rather easily. I

expandTypeSynonyms panics after kind equality patch

2016-01-06 Thread Ömer Sinan Ağacan
My branch panicking during stage 2 build and when I tried to debug I realized
the panicking function is `unionTCvSubst`, when called by `expandTypeSynonyms`.
In my branch I'm doing some type-based transformations and I'm using
`expandTypeSynonyms` on type of identifiers for that.

According to git blame logs, the function `unionTCvSubst` was added with kind
equality patch. The patch made this change in `expandTypeSynonyms`:

-  = go (mkAppTys (substTy (mkTopTvSubst tenv) rhs) tys')
+  = let subst' = unionTCvSubst subst (mkTopTCvSubst tenv) in
+go subst' (mkAppTys rhs tys')

Which is what's causing the panic. The exact place it's panicking during the
stage2 build is when I call `expandTypeSynonyms` on type `TvSubstEnv` (i.e. in
my transformation I get type of an id and it turns out to be TvSubstEnv, when I
call `expandTypeSynonyms` on this type it panics)

I figured this much but I don't understand type system details, so, does anyone
here have any ideas what's going wrong here? Richard?

Note that this panic happens even though I don't do any changes in types - I'm
just looking at the types for some transformations but no changes on the types
are done.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


NOINLINE effects worker/wrapper - why and how to fix?

2016-01-09 Thread Ömer Sinan Ağacan
So I was doing some micro benchmarks and I realized that adding NOINLINE to a
function somehow prevents worker/wrapper. Imagine this factorial function which
has a very obvious worker/wrapper opportunity:

fac :: Int -> Int
fac 0 = 1
fac n = n * fac (n - 1)

If I add NOINLINE to this, no matter what -O I use, I get this STG:

fac =
\r srt:SRT:[] [ds_s38j]
case ds_s38j of _ {
  I# ds1_s38l ->
  case ds1_s38l of ds2_s38m {
__DEFAULT ->
case -# [ds2_s38m 1#] of sat_s38n {
  __DEFAULT ->
  let { sat_s38o = NO_CCS I#! [sat_s38n];
  } in
case fac sat_s38o of _ {
  I# y_s38q ->
  case *# [ds2_s38m y_s38q] of sat_s38r {
__DEFAULT -> I# [sat_s38r];
  };
};
};
0# -> lvl_r38f;
  };
};

Which doesn't have worker/wrapper. When I remove NOINLINE I get this
worker/wrappered version as expected:

$wfac =
\r srt:SRT:[] [ww_s38W]
case ww_s38W of ds_s38X {
  __DEFAULT ->
  case -# [ds_s38X 1#] of sat_s38Y {
__DEFAULT ->
case $wfac sat_s38Y of ww1_s38Z {
  __DEFAULT -> *# [ds_s38X ww1_s38Z];
};
  };
  0# -> 1#;
};

fac =
\r srt:SRT:[] [w_s390]
case w_s390 of _ {
  I# ww1_s392 ->
  case $wfac ww1_s392 of ww2_s393 { __DEFAULT -> I#
[ww2_s393]; };
};

I'd expect to get the same with NOINLINE too. First of all, I think this
suggests that if my function is big enough (or has some other property and GHCs
heuristics decide not to inline) I don't get worker/wrapper. Second, this type
of NOINLINEs are very useful for a couple of reasons.

For example, let's say I'm benchmarking a function, I NOINLINE the function
because I don't want the function to be transformed to something else during
the benchmarking, because of inlining and interactions of the function code
with the code at the call site (the code that benchmarks).

Another example is when looking at the code to see if expected optimizations
are done by GHC. I NOINLINE because otherwise I may have to look at dozens of
call sites, rather than just one place (the definition). But now I can't
reliably do that.

So my questions are: Why worker/wrapper is not applied to NOINLINE functions,
and how do I fix this?

Thanks.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Kinds of type synonym arguments

2015-12-20 Thread Ömer Sinan Ağacan
I have another related question: What about allowing primitive types
in newtypes?

λ:4> newtype Blah1 = Blah1 Int
λ:5> newtype Blah2 = Blah2 Int#

:5:23: error:
• Expecting a lifted type, but ‘Int#’ is unlifted
• In the type ‘Int#’
  In the definition of data constructor ‘Blah2’
  In the newtype declaration for ‘Blah2’

Ideally second definition should be OK, and kind of Blah2 should be #. Is this
too hard to do?

2015-12-16 17:22 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
>
> On Dec 16, 2015, at 2:06 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:
>>
>> In any case, this is not that big deal. When I read the code I thought this
>> should be a trivial change but apparently it's not.
>
> No, it's not. Your example (`f :: (Int#, b) -> b`) still has an unboxed thing 
> in a boxed tuple. Boxed tuples simply can't (currently) hold unboxed things. 
> And changing that is far from trivial. It's not the polymorphism that's the 
> problem -- it's the unboxed thing in a boxed tuple.
>
> Richard
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: ok to do reformatting commits?

2015-11-25 Thread Ömer Sinan Ağacan
2015-11-24 22:14 GMT-05:00 Evan Laforge :
> Would anyone mind if I went and wrapped a bunch of files, say
> typecheck/*.hs?  This seems simpler than either constant hassling from
> arc or coming up with more elaborate rules for arc.  I would have to
> make some formatting decisions, so likely to some eyes I would be
> messing some stuff up, but since there's no real standard that is
> probably unavoidable.

Please don't -- like Richard I have patches in many different branches(although
they rarely touch typecheck/) and this will cause so much trouble to us.

If Arc linter is causing so much trouble(IMHO it isn't) maybe the solution is
to make Arc linter less strict.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Do we need to maintain PrimRep.VecRep?

2016-06-07 Thread Ömer Sinan Ağacan
I have some code that does things depending on PrimReps of terms and so I have
to handle VecRep there. To understand what VecRep exactly is and how to use it I
looked at its uses, and all I can find was that we have a wired-in DataCon
`vecRepDataCon` which has a type that I thought should have VecRep PrimRep, but
when I test in GHCi I see that its PrimRep is PtrRep:

λ> map typePrimRep (map dataConRepType (tyConDataCons runtimeRepTyCon))

[PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep]

(This DataCon is not exported and only used in runtimeRepTyCon)

So I think VecRep may not be in use at the moment. Do we still need to maintain
it? What's the use case? Can anyone show me a Core term that has a type whose
PrimRep is VecRep?

Thanks..
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Do we need to maintain PrimRep.VecRep?

2016-06-07 Thread Ömer Sinan Ağacan
Thanks, I can see the TyCons with VecReps there.. but I still can't see how the
terms are constructed? Can you show me some example programs, or functions in
the compiler, that generate vector terms? (e.g. terms with types with VecReps)

2016-06-07 10:48 GMT-04:00 Geoffrey Mainland <mainl...@apeiron.net>:
> VecRep is used for vector operations. If you aren't using LLVM, you
> won't see them.
>
> VecRep's are generated by utils/genprimopcode/Main.hs.
>
> Check out compiler/stage1/build/primop-vector-tys.hs-incl in your build
> tree---should be plenty of generated VecRep's there :)
>
> Cheers,
> Geoff
>
> On 06/07/2016 05:00 AM, Ömer Sinan Ağacan wrote:
>> I have some code that does things depending on PrimReps of terms and so I 
>> have
>> to handle VecRep there. To understand what VecRep exactly is and how to use 
>> it I
>> looked at its uses, and all I can find was that we have a wired-in DataCon
>> `vecRepDataCon` which has a type that I thought should have VecRep PrimRep, 
>> but
>> when I test in GHCi I see that its PrimRep is PtrRep:
>>
>> λ> map typePrimRep (map dataConRepType (tyConDataCons runtimeRepTyCon))
>> 
>> [PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep]
>>
>> (This DataCon is not exported and only used in runtimeRepTyCon)
>>
>> So I think VecRep may not be in use at the moment. Do we still need to 
>> maintain
>> it? What's the use case? Can anyone show me a Core term that has a type whose
>> PrimRep is VecRep?
>>
>> Thanks..
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Do we need to maintain PrimRep.VecRep?

2016-06-07 Thread Ömer Sinan Ağacan
Ahh, I see... I finally found the primops, machops, and code generator for x86:

  MO_V_Insert {}   -> needLlvm
  MO_V_Extract {}  -> needLlvm
  MO_V_Add {}  -> needLlvm
  MO_V_Sub {}  -> needLlvm
  ...

> The reason this is not available more widely is lack of support in the native
> code generator. Do you have any interest in working on adding such support?
> :)

I'm afraid I'm short on free time at the moment but I'll let you know if I have
a chance to work on that.

Thanks,
Omer

2016-06-07 11:22 GMT-04:00 Geoffrey Mainland <mainl...@apeiron.net>:
> Only programs that use vector primops will generate VecRep's. GHC is not
> such a program.
>
> The branch of vector that I modified to use vector primops will generate
> VecRep's. You can find it here:
>
> https://github.com/mainland/vector/tree/simd
>
> It uses a modified version of primitive. See here, for example:
>
> https://github.com/mainland/primitive/blob/simd/Data/Primitive/Multi.hs
>
> The reason this is not available more widely is lack of support in the
> native code generator. Do you have any interest in working on adding
> such support? :)
>
> Cheers,
> Geoff
>
> On 06/07/2016 11:08 AM, Ömer Sinan Ağacan wrote:
>> Thanks, I can see the TyCons with VecReps there.. but I still can't see how 
>> the
>> terms are constructed? Can you show me some example programs, or functions in
>> the compiler, that generate vector terms? (e.g. terms with types with 
>> VecReps)
>>
>> 2016-06-07 10:48 GMT-04:00 Geoffrey Mainland <mainl...@apeiron.net>:
>>> VecRep is used for vector operations. If you aren't using LLVM, you
>>> won't see them.
>>>
>>> VecRep's are generated by utils/genprimopcode/Main.hs.
>>>
>>> Check out compiler/stage1/build/primop-vector-tys.hs-incl in your build
>>> tree---should be plenty of generated VecRep's there :)
>>>
>>> Cheers,
>>> Geoff
>>>
>>> On 06/07/2016 05:00 AM, Ömer Sinan Ağacan wrote:
>>>> I have some code that does things depending on PrimReps of terms and so I 
>>>> have
>>>> to handle VecRep there. To understand what VecRep exactly is and how to 
>>>> use it I
>>>> looked at its uses, and all I can find was that we have a wired-in DataCon
>>>> `vecRepDataCon` which has a type that I thought should have VecRep 
>>>> PrimRep, but
>>>> when I test in GHCi I see that its PrimRep is PtrRep:
>>>>
>>>> λ> map typePrimRep (map dataConRepType (tyConDataCons runtimeRepTyCon))
>>>> 
>>>> [PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep,PtrRep]
>>>>
>>>> (This DataCon is not exported and only used in runtimeRepTyCon)
>>>>
>>>> So I think VecRep may not be in use at the moment. Do we still need to 
>>>> maintain
>>>> it? What's the use case? Can anyone show me a Core term that has a type 
>>>> whose
>>>> PrimRep is VecRep?
>>>>
>>>> Thanks..
>>>> ___
>>>> ghc-devs mailing list
>>>> ghc-devs@haskell.org
>>>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Force GC calls out of the straight line execution path

2016-06-13 Thread Ömer Sinan Ağacan
Hi Harendra,

Would it be possible for you to provide a minimal example that compiles to such
assembly? It's hard to tell if this is an easy case.

Also, just to make sure, you're using -O, right? (I'm not sure if we have a
related transformation enabled with -O but just to make sure...)

2016-06-13 7:23 GMT-04:00 Harendra Kumar :
> Hi,
>
> I noticed in the generated code (llvm as well as native) that in some cases
> the GC calls are in the straight path and the regular code is out of the
> straight line path. Like this:
>
> => 0x408fc0:  lea0x30(%r12),%rax
> => 0x408fc5:  cmp0x358(%r13),%rax
> => 0x408fcc:  jbe0x408fe9   # notice jbe instead of ja
> i.e. branch taken in normal case
>
> I tried to count in how many cases its happening in my executable and found
> that its only a small percentage (4-6%) of cases but those cases include the
> code which runs 99% of the time in my benchmark. Though it does not make a
> whole lot of difference but the difference is perceptible and especially
> when it is in a tight loop.
>
> Is it possible to somehow force all the GC calls out of the line during code
> generation? Has it been thought/discussed before?
>
> -harendra
>
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: CoreToStg Asserts

2016-06-14 Thread Ömer Sinan Ağacan
Hi Tamar,

Have a look at Note [Disgusting computation of CafRefs] in TidyPgm.hs. The
assertion triggered here is the one that checks `hasCafRefs` mentioned in that
note matches with actual CAF-ness.

Are you using stock GHC? Which version? Do you have a minimal program that
reproduces this?

2016-06-13 7:01 GMT-04:00 Phyx :
> Hi *,
>
> I'm hoping someone could help me understand what the asserts in CoreToStg on
> line 240 and 216 are trying to tell me.
>
> I hit both of them while trying to compile libraries as dyn.
>
> WARNING: file compiler\stgSyn\CoreToStg.hs, line 250
>   $trModule2 False True
> ghc-stage1.exe: panic! (the 'impossible' happened)
>   (GHC version 8.1.20160612 for x86_64-unknown-mingw32):
> ASSERT failed!
>   file compiler\stgSyn\CoreToStg.hs line 216 $trModule2
>
> Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
>
> WARNING: file compiler\simplCore\SimplCore.hs, line 633
>   Simplifier bailing out after 4 iterations [6737, 736, 51, 9]
> Size = {terms: 12,990, types: 9,998, coercions: 443}
> WARNING: file compiler\stgSyn\CoreToStg.hs, line 250
>   $fEqBigNat_$c/= False True
> ghc-stage1.exe: panic! (the 'impossible' happened)
>   (GHC version 8.1.20160612 for x86_64-unknown-mingw32):
> ASSERT failed!
>   file compiler\stgSyn\CoreToStg.hs line 240
>   [$fEqBigNat_$c/=, $fEqBigNat]
>
> Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug
>
> Kind Regards,
> Tamar
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


comment lines in Cmm outputs

2016-05-28 Thread Ömer Sinan Ağacan
I'm reading a lot of Cmm  these days and comments added by Cmm dump (which are
apparently added after 8.0.1) are so annoying becuase they're not saying
anything useful (what's the point of adding "// CmmCall" to a "call" line or
"// CmmCondBranch" to a "if" line?) but making a lot of noise. Why were those
added? Can we remove them?
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


can't build with release settings

2016-05-28 Thread Ömer Sinan Ağacan
Is anyone else having this problem when building with default settings
(no build.mk):

"inplace/bin/ghc-stage2" -hisuf dyn_hi -osuf  dyn_o -hcsuf dyn_hc
-fPIC -dynamic  -H32m -O -Wall  -hide-all-packages -i
-iutils/haddock/driver -iutils/haddock/haddock-api/src
-iutils/haddock/haddock-library/vendor/attoparsec-0.12.1.1
-iutils/haddock/haddock-library/src -iutils/haddock/dist/build
-iutils/haddock/dist/build/autogen -Iutils/haddock/dist/build
-Iutils/haddock/dist/build/autogen-optP-DIN_GHC_TREE -optP-include
-optPutils/haddock/dist/build/autogen/cabal_macros.h -package-id
Cabal-1.25.0.0 -package-id array-0.5.1.1 -package-id base-4.9.0.0
-package-id bytestring-0.10.8.1 -package-id containers-0.5.7.1
-package-id deepseq-1.4.2.0 -package-id directory-1.2.6.2 -package-id
filepath-1.4.1.0 -package-id ghc-8.1 -package-id ghc-boot-8.1
-package-id transformers-0.5.2.0 -package-id xhtml-3000.2.1
-funbox-strict-fields -Wall -fwarn-tabs -O2 -threaded -XHaskell2010
-no-user-package-db -rtsopts -Wno-unused-imports -Wno-deprecations
-Wnoncanonical-monad-instances  -odir utils/haddock/dist/build -hidir
utils/haddock/dist/build -stubdir utils/haddock/dist/build-c
utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs -o
utils/haddock/dist/build/Documentation/Haddock/Types.dyn_o

utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:15:8:
error:
Failed to load interface for ‘Prelude’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:17:1:
error:
Failed to load interface for ‘Data.Foldable’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:18:1:
error:
Failed to load interface for ‘Data.Traversable’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/driver/ResponseFile.hs:2:8: error:
Failed to load interface for ‘Prelude’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/driver/ResponseFile.hs:8:1: error:
Failed to load interface for ‘Control.Exception’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/driver/ResponseFile.hs:9:1: error:
Failed to load interface for ‘Data.Char’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/driver/ResponseFile.hs:10:1: error:
Failed to load interface for ‘Data.Foldable’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/driver/ResponseFile.hs:11:1: error:
Failed to load interface for ‘System.Exit’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/driver/ResponseFile.hs:12:1: error:
Failed to load interface for ‘System.IO’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.


utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:16:8:
error:utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs:1:8:
error:
Failed to load interface for ‘Prelude’

It is a member of the hidden packageFailed to load
interface for ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.
 ‘Prelude’

It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:19:1: error:
Failed to load interface for ‘Control.Arrow’
It is a member of the hidden package ‘base-4.9.0.0’.
Use -v to see a list of the files searched for.

utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs:4:1:
error:utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:20:1: error:
Failed to load interface for
Failed to load interface for ‘GHC’
 ‘Data.Function’
It is a member of the hidden packageIt is a member of the
hidden package ‘base-4.9.0.0’.
 ‘ghc-8.1’.
Use -v to see a list of the files searched for.
Use -v to see a list of the files searched for.

utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:22:1: error:
Failed to load interface for ‘Exception’
It is a member of the hidden package ‘ghc-8.1’.
Use -v to see a list of the files searched for.

utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:23:1: error:
Failed to load interface for ‘Outputable’
It is a member of the hidden package ‘ghc-8.1’.

Re: can't build with release settings

2016-05-28 Thread Ömer Sinan Ağacan
I just had the same error when I checkout current HEAD. (without a
distclean though)

2016-05-28 14:56 GMT-04:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
> Is anyone else having this problem when building with default settings
> (no build.mk):
>
> "inplace/bin/ghc-stage2" -hisuf dyn_hi -osuf  dyn_o -hcsuf dyn_hc
> -fPIC -dynamic  -H32m -O -Wall  -hide-all-packages -i
> -iutils/haddock/driver -iutils/haddock/haddock-api/src
> -iutils/haddock/haddock-library/vendor/attoparsec-0.12.1.1
> -iutils/haddock/haddock-library/src -iutils/haddock/dist/build
> -iutils/haddock/dist/build/autogen -Iutils/haddock/dist/build
> -Iutils/haddock/dist/build/autogen-optP-DIN_GHC_TREE -optP-include
> -optPutils/haddock/dist/build/autogen/cabal_macros.h -package-id
> Cabal-1.25.0.0 -package-id array-0.5.1.1 -package-id base-4.9.0.0
> -package-id bytestring-0.10.8.1 -package-id containers-0.5.7.1
> -package-id deepseq-1.4.2.0 -package-id directory-1.2.6.2 -package-id
> filepath-1.4.1.0 -package-id ghc-8.1 -package-id ghc-boot-8.1
> -package-id transformers-0.5.2.0 -package-id xhtml-3000.2.1
> -funbox-strict-fields -Wall -fwarn-tabs -O2 -threaded -XHaskell2010
> -no-user-package-db -rtsopts -Wno-unused-imports -Wno-deprecations
> -Wnoncanonical-monad-instances  -odir utils/haddock/dist/build -hidir
> utils/haddock/dist/build -stubdir utils/haddock/dist/build-c
> utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs -o
> utils/haddock/dist/build/Documentation/Haddock/Types.dyn_o
>
> utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:15:8:
> error:
> Failed to load interface for ‘Prelude’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:17:1:
> error:
> Failed to load interface for ‘Data.Foldable’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:18:1:
> error:
> Failed to load interface for ‘Data.Traversable’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/driver/ResponseFile.hs:2:8: error:
> Failed to load interface for ‘Prelude’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/driver/ResponseFile.hs:8:1: error:
> Failed to load interface for ‘Control.Exception’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/driver/ResponseFile.hs:9:1: error:
> Failed to load interface for ‘Data.Char’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/driver/ResponseFile.hs:10:1: error:
> Failed to load interface for ‘Data.Foldable’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/driver/ResponseFile.hs:11:1: error:
> Failed to load interface for ‘System.Exit’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/driver/ResponseFile.hs:12:1: error:
> Failed to load interface for ‘System.IO’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
>
> utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:16:8:
> error:utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs:1:8:
> error:
> Failed to load interface for ‘Prelude’
>
> It is a member of the hidden packageFailed to load
> interface for ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>  ‘Prelude’
>
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:19:1: error:
> Failed to load interface for ‘Control.Arrow’
> It is a member of the hidden package ‘base-4.9.0.0’.
> Use -v to see a list of the files searched for.
>
> utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs:4:1:
> error:utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:20:1: error:
> Failed to load interface for
> Failed to load interface for ‘GHC’
>  ‘Data.Function’

Re: can't build with release settings

2016-05-28 Thread Ömer Sinan Ağacan
Please ignore. I realized I had a bug in my code (which makes some
changes in generated Cmm) and I realized -DDEBUG is not on for stage1
in release mode, so my assertions were not running. I have no idea how
can the bug cause this error though...

2016-05-28 15:03 GMT-04:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
> I just had the same error when I checkout current HEAD. (without a
> distclean though)
>
> 2016-05-28 14:56 GMT-04:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
>> Is anyone else having this problem when building with default settings
>> (no build.mk):
>>
>> "inplace/bin/ghc-stage2" -hisuf dyn_hi -osuf  dyn_o -hcsuf dyn_hc
>> -fPIC -dynamic  -H32m -O -Wall  -hide-all-packages -i
>> -iutils/haddock/driver -iutils/haddock/haddock-api/src
>> -iutils/haddock/haddock-library/vendor/attoparsec-0.12.1.1
>> -iutils/haddock/haddock-library/src -iutils/haddock/dist/build
>> -iutils/haddock/dist/build/autogen -Iutils/haddock/dist/build
>> -Iutils/haddock/dist/build/autogen-optP-DIN_GHC_TREE -optP-include
>> -optPutils/haddock/dist/build/autogen/cabal_macros.h -package-id
>> Cabal-1.25.0.0 -package-id array-0.5.1.1 -package-id base-4.9.0.0
>> -package-id bytestring-0.10.8.1 -package-id containers-0.5.7.1
>> -package-id deepseq-1.4.2.0 -package-id directory-1.2.6.2 -package-id
>> filepath-1.4.1.0 -package-id ghc-8.1 -package-id ghc-boot-8.1
>> -package-id transformers-0.5.2.0 -package-id xhtml-3000.2.1
>> -funbox-strict-fields -Wall -fwarn-tabs -O2 -threaded -XHaskell2010
>> -no-user-package-db -rtsopts -Wno-unused-imports -Wno-deprecations
>> -Wnoncanonical-monad-instances  -odir utils/haddock/dist/build -hidir
>> utils/haddock/dist/build -stubdir utils/haddock/dist/build-c
>> utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs -o
>> utils/haddock/dist/build/Documentation/Haddock/Types.dyn_o
>>
>> utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:15:8:
>> error:
>> Failed to load interface for ‘Prelude’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>> utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:17:1:
>> error:
>> Failed to load interface for ‘Data.Foldable’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>> utils/haddock/haddock-library/src/Documentation/Haddock/Types.hs:18:1:
>> error:
>> Failed to load interface for ‘Data.Traversable’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>> utils/haddock/driver/ResponseFile.hs:2:8: error:
>> Failed to load interface for ‘Prelude’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>> utils/haddock/driver/ResponseFile.hs:8:1: error:
>> Failed to load interface for ‘Control.Exception’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>> utils/haddock/driver/ResponseFile.hs:9:1: error:
>> Failed to load interface for ‘Data.Char’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>> utils/haddock/driver/ResponseFile.hs:10:1: error:
>> Failed to load interface for ‘Data.Foldable’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>> utils/haddock/driver/ResponseFile.hs:11:1: error:
>> Failed to load interface for ‘System.Exit’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>> utils/haddock/driver/ResponseFile.hs:12:1: error:
>> Failed to load interface for ‘System.IO’
>> It is a member of the hidden package ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>
>>
>> utils/haddock/haddock-api/src/Haddock/GhcUtils.hs:16:8:
>> error:utils/haddock/haddock-api/src/Haddock/Backends/Hyperlinker/Types.hs:1:8:
>> error:
>> Failed to load interface for ‘Prelude’
>>
>> It is a member of the hidden packageFailed to load
>> interface for ‘base-4.9.0.0’.
>> Use -v to see a list of the files searched for.
>>  ‘Prelude’
>

Re: comment lines in Cmm outputs

2016-05-29 Thread Ömer Sinan Ağacan
Wait, isn't new codegen merged years ago? I don't see these comment
lines in 8.0.1-generated Cmm files. Comments in the AST may be there
but no comments were printed until very recently.

If no one feels strongly about this I'd love to remove those.

2016-05-29 11:14 GMT-04:00 Ben Gamari <b...@smart-cactus.org>:
> Ömer Sinan Ağacan <omeraga...@gmail.com> writes:
>
>> I'm reading a lot of Cmm  these days and comments added by Cmm dump (which 
>> are
>> apparently added after 8.0.1) are so annoying becuase they're not saying
>> anything useful (what's the point of adding "// CmmCall" to a "call" line or
>> "// CmmCondBranch" to a "if" line?) but making a lot of noise. Why were those
>> added? Can we remove them?
>
> It looks like they've been with us since the initial merge of the new
> codegen. I agree that they don't add much value but I don't have any
> strong opinion either way. The only comment that we might want to
> retain is the one for CmmUnsafeForeignCall as it looks quite similar to
> a CmmCall.
>
> Cheers,
>
> - Ben
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: comment lines in Cmm outputs

2016-05-29 Thread Ömer Sinan Ağacan
2016-05-29 11:14 GMT-04:00 Ben Gamari :
> CmmUnsafeForeignCall as it looks quite similar to
> a CmmCall

Well then maybe we should print those differently instead of adding
noise to every single line just to distinguish CmmUnsafeForeignCall
from CmmCall.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Core of a whole package

2016-05-31 Thread Ömer Sinan Ağacan
2016-05-31 16:04 GMT-04:00 Alberto Sadde O. :
> I am trying to get the Core of a whole package.
> I have been using the GHC API to get the Core of each file in a package but
> I have a problems with non-exposed modules of the package.

Try `cabal install --ghc-options="-ddump-simpl -ddump-to-file"`. You
should see Core outputs under `dist/`.
(or `cabal configure --ghc-options=...` then `cabal build`)

If you have all the dependencies installed already you can just do
`ghc --make Main.hs -fforce-recomp -ddump-simpl -ddump-to-file` where
`Main.hs` imports all the modules in your project.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Core of a whole package

2016-06-01 Thread Ömer Sinan Ağacan
You have to do your manipulations module by module, as GHC is doing compilation
that way. If you need some information from other modules when compiling a
module, you should dump that information in .hi files (like definitions of
inline functions).

What exactly are you trying to do?

2016-05-31 17:56 GMT-04:00 Alberto Sadde O. :
>
>>
>> 2016-05-31 16:04 GMT-04:00 Alberto Sadde O. :
>> > I am trying to get the Core of a whole package.
>> > I have been using the GHC API to get the Core of each file in a package
>> > but
>> > I have a problems with non-exposed modules of the package.
>>
>> Try `cabal install --ghc-options="-ddump-simpl -ddump-to-file"`. You
>> should see Core outputs under `dist/`.
>> (or `cabal configure --ghc-options=...` then `cabal build`)
>>
>> If you have all the dependencies installed already you can just do
>> `ghc --make Main.hs -fforce-recomp -ddump-simpl -ddump-to-file` where
>> `Main.hs` imports all the modules in your project.
>
>
> Thanks for the answer.
> The thing is that I want to manipulate the Core of the package not just
> simply dump it to a file.
>
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Core of a whole package

2016-06-01 Thread Ömer Sinan Ağacan
> So how do I dump the contents of a module to a .hi file? Is this
> something I can do through the API?

I'm not saying you can at the moment, I'm just saying usually if you need some
cross-module sharing you put the stuff you want to read when compiling other
files in .hi files as those files are read when compiling other modules.

In you case I think you can just keep a file, write your module-level stats
there and then run a post-compilation pass to generate final stats.

2016-06-01 3:35 GMT-04:00 Alberto Sadde O. <albertosa...@gmail.com>:
> I am trying to extract information at the Core level about which functions
> are the most used within a package, which data types are the most used.
>
> So how do I dump the contents of a module to a .hi file? Is this something I
> can do through the API?
>
>
>
> Alberto
>
>
> On Wed, Jun 1, 2016 at 8:31 AM, Ömer Sinan Ağacan <omeraga...@gmail.com>
> wrote:
>>
>> You have to do your manipulations module by module, as GHC is doing
>> compilation
>> that way. If you need some information from other modules when compiling a
>> module, you should dump that information in .hi files (like definitions of
>> inline functions).
>>
>> What exactly are you trying to do?
>>
>> 2016-05-31 17:56 GMT-04:00 Alberto Sadde O. <albertosa...@gmail.com>:
>> >
>> >>
>> >> 2016-05-31 16:04 GMT-04:00 Alberto Sadde O. <albertosa...@gmail.com>:
>> >> > I am trying to get the Core of a whole package.
>> >> > I have been using the GHC API to get the Core of each file in a
>> >> > package
>> >> > but
>> >> > I have a problems with non-exposed modules of the package.
>> >>
>> >> Try `cabal install --ghc-options="-ddump-simpl -ddump-to-file"`. You
>> >> should see Core outputs under `dist/`.
>> >> (or `cabal configure --ghc-options=...` then `cabal build`)
>> >>
>> >> If you have all the dependencies installed already you can just do
>> >> `ghc --make Main.hs -fforce-recomp -ddump-simpl -ddump-to-file` where
>> >> `Main.hs` imports all the modules in your project.
>> >
>> >
>> > Thanks for the answer.
>> > The thing is that I want to manipulate the Core of the package not just
>> > simply dump it to a file.
>> >
>> >
>> >
>
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Parser changes for supporting top-level SCC annotations

2016-06-01 Thread Ömer Sinan Ağacan
I was actually trying to avoid that, thinking that it'd be best if SCC uniformly
worked for top-levels and expressions. But then this new form:

{-# SCC f "f_scc" #-}

Would only work for toplevel SCCs.. So maybe it's OK to introduce a new pragma
here.

2016-06-01 8:13 GMT-04:00 Richard Eisenberg <e...@cis.upenn.edu>:
> What about just using a new pragma?
>
>> {-# SCC_FUNCTION f "f_scc" #-}
>> f True = ...
>> f False = ...
>
> The pragma takes the name of the function (a single identifier) and the name 
> of the SCC. If you wish both to have the same name, you can leave off the SCC 
> name.
>
> It seems worth it to me to introduce a new pragma here.
>
> Richard
>
> On May 30, 2016, at 3:14 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:
>
>> I'm trying to support SCCs at the top-level. The implementation should be
>> trivial except the parsing part turned out to be tricky. Since expressions 
>> can
>> appear at the top-level, after a {-# SCC ... #-} parser can't decide whether 
>> to
>> reduce the token in `sigdecl` to generate a `(LHsDecl (Sig (SCCSig ...)))` 
>> or to
>> keep shifting to parse an expression. As shifting is the default behavior 
>> when a
>> shift/reduce conflict happens, it's always trying to parse an expression, 
>> which
>> is always the wrong thing to do.
>>
>> Does anyone have any ideas on how to handle this?
>>
>> Motivation: Not having SCCs at the top level is becoming annoying real quick.
>> For simplest cases, it's possible to do this transformation:
>>
>>f x y = ...
>>=>
>>f = {-# SCC f #-} \x y -> ...
>>
>> However, it doesn't work when there's a `where` clause:
>>
>>f x y = 
>>  where t = ...
>>=>
>>f = {-# SCC f #-} \x y -> 
>>  where t = ...
>>
>> Or when we have a "equation style" definition:
>>
>>f (C1 ...) = ...
>>f (C2 ...) = ...
>>f (C3 ...) = ...
>>...
>>
>> (usual solution is to rename `f` to `f'` and define a new `f` with a `SCC`)
>> ___
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Parser changes for supporting top-level SCC annotations

2016-05-30 Thread Ömer Sinan Ağacan
I'm trying to support SCCs at the top-level. The implementation should be
trivial except the parsing part turned out to be tricky. Since expressions can
appear at the top-level, after a {-# SCC ... #-} parser can't decide whether to
reduce the token in `sigdecl` to generate a `(LHsDecl (Sig (SCCSig ...)))` or to
keep shifting to parse an expression. As shifting is the default behavior when a
shift/reduce conflict happens, it's always trying to parse an expression, which
is always the wrong thing to do.

Does anyone have any ideas on how to handle this?

Motivation: Not having SCCs at the top level is becoming annoying real quick.
For simplest cases, it's possible to do this transformation:

f x y = ...
=>
f = {-# SCC f #-} \x y -> ...

However, it doesn't work when there's a `where` clause:

f x y = 
  where t = ...
=>
f = {-# SCC f #-} \x y -> 
  where t = ...

Or when we have a "equation style" definition:

f (C1 ...) = ...
f (C2 ...) = ...
f (C3 ...) = ...
...

(usual solution is to rename `f` to `f'` and define a new `f` with a `SCC`)
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Does anyone know any easy-to-run compile-time benchmark suites?

2016-06-23 Thread Ömer Sinan Ağacan
Hi all,

I was wondering if anyone has or knows easy-to-run compile-time benchmarks? I'm
looking for something like nofib -- ideally after a fresh build I should be
able to just run `make` and get some numbers (mainly allocations) back.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Testsuite cleaning

2016-06-24 Thread Ömer Sinan Ağacan
I also realized this after a rebase I did yesterday. Should be a recent thing.

2016-06-24 7:58 GMT+00:00 Simon Peyton Jones via ghc-devs
:
> Thomas
>
> During debugging I often compile a single test program
>
> ghc -c T1969.hs
>
> But the new testsuite setup doesn’t remove .hi and .o files before running a
> test, so
>
> make TEST=T1969
>
> says
>
> bytes allocated value is too low:
>
> …
>
> Deviation   T1969(normal) bytes allocated: -95.2 %
>
> Reason?  Compilation was not required!
>
> Non-perf tests fail in the same way
>
> +compilation IS NOT required
>
> *** unexpected failure for T11480b(normal)
>
> I’m sure this didn’t use to happen.
>
> It’s not fatal, because can manually remove those .o files, but it’s a bit
> of a nuisance.  Might it be easy to restore the old behaviour?
>
> Thanks
>
> Simon
>
>
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


How to build profiled stage1?

2016-01-18 Thread Ömer Sinan Ağacan
I'm trying to debug my stage1 compiler and as a last resort I'm trying to build
stage1 compiler using `-prof -fprof-auto` to be able to do `+RTS -xc -RTS`
during the stage2 build.

I tried couple of things but they all failed in different ways.

As far as I understand, both SRC_HC_OPTS and GhcStage1HcOpts are passed to
system-wide installed ghc during the stage1 build and libraries. So I do one of
these changes:

SRC_HC_OPTS= -O -H64m -prof -fprof-auto
GhcStage1HcOpts= -O0 -DDEBUG -prof -fprof-auto

The second change I want to make is I want to pass `+RTS -xc -RTS` to
ghc-stage1, for that I'm making this change:

GhcLibHcOpts   = -O -dcore-lint -prof -fprof-auto

But, no matter what else I change, I can't get past this stage:

"/usr/local/bin/ghc" -hisuf hi -osuf  o -hcsuf hc -static  -O
-H64m  -Wall   -package-db libraries/bootstrapping.conf
-this-package-key ghc-8.1 -hide-all-packages -i -icompiler/basicTypes
-icompiler/cmm -icompiler/codeGen -icompiler/coreSyn
-icompiler/deSugar -icompiler/ghci -icompiler/hsSyn -icompiler/iface
-icompiler/llvmGen -icompiler/main -icompiler/nativeGen
-icompiler/parser -icompiler/prelude -icompiler/profiling
-icompiler/rename -icompiler/simplCore -icompiler/simplStg
-icompiler/specialise -icompiler/stgSyn -icompiler/stranal
-icompiler/typecheck -icompiler/types -icompiler/utils
-icompiler/vectorise -icompiler/stage1/build
-icompiler/stage1/build/autogen -Icompiler/stage1/build
-Icompiler/stage1/build/autogen -Icompiler/. -Icompiler/parser
-Icompiler/utils -Icompiler/stage1-optP-include
-optPcompiler/stage1/build/autogen/cabal_macros.h -package-id
array-0.5.1.0-960bf9ae8875cc30355e086f8853a049 -package-id
base-4.8.2.0-0d6d1084fbc041e1cded9228e80e264d -package-id
binary-0.8.0.0 -package-id
bytestring-0.10.6.0-9a873bcf33d6ce2fd2698ce69e2c1c66 -package-id
containers-0.5.6.2-59326c33e30ec8f6afd574cbac625bbb -package-id
directory-1.2.2.0-660a7a83a753ed85c8a374c15dae2b97 -package-id
filepath-1.4.0.0-f97d1e4aebfd7a03be6980454fe31d6e -package-id
ghc-boot-8.1 -package-id hoopl-3.10.2.1 -package-id hpc-0.6.0.3
-package-id process-1.2.3.0-a22328103774f0499a990653944cbf99
-package-id template-haskell-2.11.0.0 -package-id
time-1.5.0.1-1b9a502bb07a3e6f4d6935fbf9db7181 -package-id
transformers-0.5.0.0 -package-id
unix-2.7.1.0-bb54ee8f9f6b2600aae7a748eb88a610 -Wall
-fno-warn-name-shadowing -this-package-key ghc -XHaskell2010 -DSTAGE=1
-Rghc-timing -O0 -DDEBUG -prof -fprof-auto  -no-user-package-db
-rtsopts   -odir compiler/stage1/build -hidir
compiler/stage1/build -stubdir compiler/stage1/build-c
compiler/utils/Exception.hs -o compiler/stage1/build/Exception.o

compiler/utils/Exception.hs:10:1:
Failed to load interface for ‘Control.Monad.IO.Class’
Perhaps you haven't installed the profiling libraries for
package ‘transformers-0.5.0.0’?
Use -v to see a list of the files searched for.
<>

I tried enabling library-profiling in my global Cabal config, but that didn't
help. Any ideas how to do this?

If it matters, I'm on Linux.

NOTE: If I pass -v to GHC, it lists this place in the list of
locations searched:


/home/omer/haskell/ghc_unboxed_sums/libraries/transformers/dist-boot/build/Control/Monad/IO/Class.p_hi

Indeed, the file is not there. When I look at all the command the build system
run at this point, I see lines like this:

"/usr/local/bin/ghc-pkg" update --force
--package-db=libraries/bootstrapping.conf
libraries/transformers/dist-boot/inplace-pkg-config
Reading package info from
"libraries/transformers/dist-boot/inplace-pkg-config" ... done.
transformers-0.5.0.0: Warning: Unrecognized field abi on line 47
transformers-0.5.0.0: Warning: haddock-interfaces:
/home/omer/haskell/ghc_unboxed_sums/libraries/transformers/dist-boot/doc/html/transformers/transformers.haddock
doesn't exist or isn't a file
transformers-0.5.0.0: cannot find any of
["Control/Applicative/Backwards.hi","Control/Applicative/Backwards.p_hi","Control/Applicative/Backwards.dyn_hi"]
(ignoring)
transformers-0.5.0.0: cannot find any of
["Control/Applicative/Lift.hi","Control/Applicative/Lift.p_hi","Control/Applicative/Lift.dyn_hi"]
(ignoring)
transformers-0.5.0.0: cannot find any of
["Control/Monad/Signatures.hi","Control/Monad/Signatures.p_hi","Control/Monad/Signatures.dyn_hi"]
(ignoring)
transformers-0.5.0.0: cannot find any of
["Control/Monad/Trans/Class.hi","Control/Monad/Trans/Class.p_hi","Control/Monad/Trans/Class.dyn_hi"]
(ignoring)
transformers-0.5.0.0: cannot find any of
["Control/Monad/Trans/Cont.hi","Control/Monad/Trans/Cont.p_hi","Control/Monad/Trans/Cont.dyn_hi"]
(ignoring)
transformers-0.5.0.0: cannot find any of
["Control/Monad/Trans/Except.hi","Control/Monad/Trans/Except.p_hi","Control/Monad/Trans/Except.dyn_hi"]
(ignoring)
transformers-0.5.0.0: cannot find any of
["Control/Monad/Trans/Error.hi","Control/Monad/Trans/Error.p_hi","Control/Monad/Trans/Error.dyn_hi"]
(ignoring)

Re: StgCase - are LiveVars and SRT fields going to be used?

2016-02-06 Thread Ömer Sinan Ağacan
I submitted https://phabricator.haskell.org/D1889 which hopefully
fixes this properly.

2016-02-05 21:50 GMT-05:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
> Simon, I broke the debug build with that commit. I actually validated locally
> before committing, but apparently the default validate settings doesn't define
> DEBUG, so the new assertion implementation was not tested. (Why validate
> doesn't define DEBUG by default???)
>
> The fastest way to reproduce the bug is to use these validate settings:
>
> DYNAMIC_GHC_PROGRAMS = NO
> GhcLibWays = v
> GhcStage1HcOpts += -DDEBUG
>
> I did some debugging. Here's an example definition that causes the assertion
> failure:
>
>   unpackCString#
>   unpackCString# [InlPrag=NOINLINE] :: Addr# -> [Char]
>   [GblId,
>Arity=1,
>Caf=NoCafRefs,
>Str=DmdType <S,U>,
>Unf=OtherCon []] =
>   \r [addr_seX]
>   let {
> unpack_seY [Occ=LoopBreaker] :: Int# -> [Char]
> [LclId, Arity=1, Str=DmdType <S,U>, Unf=OtherCon []] =
> sat-only \r [nh_seZ]
> case indexCharOffAddr# [addr_seX nh_seZ] of ch_sf0 {
>   __DEFAULT ->
>   let {
> sat_sf3 [Occ=Once] :: [Char]
> [LclId, Str=DmdType] =
> \u []
> case +# [nh_seZ 1#] of sat_sf2 {
>   __DEFAULT -> unpack_seY sat_sf2;
> }; } in
>   let {
> sat_sf1 [Occ=Once] :: Char
> [LclId, Str=DmdType] =
> NO_CCS C#! [ch_sf0];
>   } in  : [sat_sf1 sat_sf3];
>   '\NUL'# -> [] [];
> };
>   } in  unpack_seY 0#;
>
> Here the IdInfo says this doesn't have CAF refs, but `sat_sf3` is updatable, 
> so
> in our assertion we say that this has a CAF. In the implementation I basically
> followed your description:
>
> "
> - If the binding is an updatable thunk, it has CAF refs.
>
> - Otherwise it has CAF reffs iff any of its free Ids (including imported ones)
>   has mayHaveCafRefs in its IdInfo. Actually you can probably ignore the 
> "free"
>   part and just check if any Id has mayHaveCafRefs set.
> "
>
> The first case is why we say "yes" to stgBindHasCafRefs. But I don't quite
> understand why we say every updatable thunk has CAFs. I think this is only the
> case with top-level updatable thunks, right? If no, then maybe the problem is
> not with the assertion but rather with the CorePrep step that sets IdInfos? 
> Any
> ideas?
>
> Thanks..
>
> 2016-02-01 20:19 GMT-05:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
>> https://phabricator.haskell.org/D1880
>>
>> 2016-02-01 18:04 GMT-05:00 Simon Peyton Jones <simo...@microsoft.com>:
>>> Those fields are dead, now that the Cmm pass deals with it.  We left it in 
>>> while making the transition, but they can go now.  Go ahead!
>>>
>>> (Lots of code should disappear along with them!)
>>>
>>> Simon
>>>
>>> | -Original Message-
>>> | From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ömer 
>>> Sinan
>>> | Agacan
>>> | Sent: 01 February 2016 22:06
>>> | To: ghc-devs <ghc-devs@haskell.org>
>>> | Subject: StgCase - are LiveVars and SRT fields going to be used?
>>> |
>>> | Hi all,
>>> |
>>> | This is how case expression in STG currently defined:
>>> |
>>> |
>>> |   | StgCase
>>> | (GenStgExpr bndr occ)
>>> | (GenStgLiveVars occ)
>>> | (GenStgLiveVars occ)
>>> | bndr
>>> | SRT
>>> | AltType
>>> | [GenStgAlt bndr occ]
>>> |
>>> |
>>> | The GenStgLiveVars and SRT fields are never used anywhere in the compiler
>>> | (except the printer). So the question is, I'm assuming those were used at
>>> | some
>>> | point, but are they going to be used in the future? Or can I just delete
>>> | those?
>>> |
>>> | As a proof of concept, I just compiled GHC using this:
>>> |
>>> |
>>> |   | StgCase
>>> | (GenStgExpr bndr occ)
>>> | bndr
>>>

Re: StgCase - are LiveVars and SRT fields going to be used?

2016-02-05 Thread Ömer Sinan Ağacan
Simon, I broke the debug build with that commit. I actually validated locally
before committing, but apparently the default validate settings doesn't define
DEBUG, so the new assertion implementation was not tested. (Why validate
doesn't define DEBUG by default???)

The fastest way to reproduce the bug is to use these validate settings:

DYNAMIC_GHC_PROGRAMS = NO
GhcLibWays = v
GhcStage1HcOpts += -DDEBUG

I did some debugging. Here's an example definition that causes the assertion
failure:

  unpackCString#
  unpackCString# [InlPrag=NOINLINE] :: Addr# -> [Char]
  [GblId,
   Arity=1,
   Caf=NoCafRefs,
   Str=DmdType <S,U>,
   Unf=OtherCon []] =
  \r [addr_seX]
  let {
unpack_seY [Occ=LoopBreaker] :: Int# -> [Char]
[LclId, Arity=1, Str=DmdType <S,U>, Unf=OtherCon []] =
sat-only \r [nh_seZ]
case indexCharOffAddr# [addr_seX nh_seZ] of ch_sf0 {
  __DEFAULT ->
  let {
sat_sf3 [Occ=Once] :: [Char]
[LclId, Str=DmdType] =
\u []
case +# [nh_seZ 1#] of sat_sf2 {
  __DEFAULT -> unpack_seY sat_sf2;
}; } in
  let {
sat_sf1 [Occ=Once] :: Char
[LclId, Str=DmdType] =
NO_CCS C#! [ch_sf0];
  } in  : [sat_sf1 sat_sf3];
  '\NUL'# -> [] [];
};
  } in  unpack_seY 0#;

Here the IdInfo says this doesn't have CAF refs, but `sat_sf3` is updatable, so
in our assertion we say that this has a CAF. In the implementation I basically
followed your description:

"
- If the binding is an updatable thunk, it has CAF refs.

- Otherwise it has CAF reffs iff any of its free Ids (including imported ones)
  has mayHaveCafRefs in its IdInfo. Actually you can probably ignore the "free"
  part and just check if any Id has mayHaveCafRefs set.
"

The first case is why we say "yes" to stgBindHasCafRefs. But I don't quite
understand why we say every updatable thunk has CAFs. I think this is only the
case with top-level updatable thunks, right? If no, then maybe the problem is
not with the assertion but rather with the CorePrep step that sets IdInfos? Any
ideas?

Thanks..

2016-02-01 20:19 GMT-05:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
> https://phabricator.haskell.org/D1880
>
> 2016-02-01 18:04 GMT-05:00 Simon Peyton Jones <simo...@microsoft.com>:
>> Those fields are dead, now that the Cmm pass deals with it.  We left it in 
>> while making the transition, but they can go now.  Go ahead!
>>
>> (Lots of code should disappear along with them!)
>>
>> Simon
>>
>> | -Original Message-
>> | From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ömer 
>> Sinan
>> | Agacan
>> | Sent: 01 February 2016 22:06
>> | To: ghc-devs <ghc-devs@haskell.org>
>> | Subject: StgCase - are LiveVars and SRT fields going to be used?
>> |
>> | Hi all,
>> |
>> | This is how case expression in STG currently defined:
>> |
>> |
>> |   | StgCase
>> | (GenStgExpr bndr occ)
>> | (GenStgLiveVars occ)
>> | (GenStgLiveVars occ)
>> | bndr
>> | SRT
>> | AltType
>> | [GenStgAlt bndr occ]
>> |
>> |
>> | The GenStgLiveVars and SRT fields are never used anywhere in the compiler
>> | (except the printer). So the question is, I'm assuming those were used at
>> | some
>> | point, but are they going to be used in the future? Or can I just delete
>> | those?
>> |
>> | As a proof of concept, I just compiled GHC using this:
>> |
>> |
>> |   | StgCase
>> | (GenStgExpr bndr occ)
>> | bndr
>> | AltType
>> | [GenStgAlt bndr occ]
>> |
>> |
>> | Normally this is not a big deal, but I'm doing lots of STG-to-STG
>> | transformations nowadays, and I have to keep those field updated which is
>> | annoying as those are never going to be used (I can't even know if I'm 
>> doing
>> | it
>> | right), or leave those `undefined` which is not a good practice.
>> | ___
>> | ghc-devs mailing list
>> | ghc-devs@haskell.org
>> | 
>> https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.
>> | org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
>> | 
>> devs=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c12ca56c8fc514f477f7f08
>> | 
>> d32b53f4bc%7c72f988bf86f141af91ab2d7cd011db47%7c1=LPiupNbUJ9OGL9cmbP%2f
>> | PAs2JSdxqlxk%2bGbXuYTHFbzg%3d
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: a reliable way of dropping levity args?

2016-01-29 Thread Ömer Sinan Ağacan
2016-01-29 3:36 GMT-05:00 Simon Peyton Jones :
>
> So you need something like
>
> isLevityCon :: Type -> Bool
> isLevityCon (TyConApp tc []) = isLevityTy (tyConKind tc)
> ..
>
> Please document both functions carefully
>
> ALSO there is a bug in isLevityTy; it is missing a coreView test.  Would you 
> like to fix this?

Just submitted a patch: https://phabricator.haskell.org/D1867
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: a reliable way of dropping levity args?

2016-01-28 Thread Ömer Sinan Ağacan
I finally had some time to have another look. I have this line in my
compiler pass:

| Just (tc, args) <- splitTyConApp_maybe ty
, isUnboxedTupleTyCon tc
= pprTrace "elimUbxSumRepTypes"
(text "orig args:" <+> ppr args $$
 text "dropWhile isLevityTy args = " <+> ppr (dropWhile
isLevityTy args)) $
  concatMap go (drop (length args `div` 2) args)

This is one of the outputs:

elimUbxSumRepTypes
  orig args: ['Lifted, 'Lifted, 'Lifted, String, String, String]
  dropWhile isLevityTy args =  ['Lifted, 'Lifted, 'Lifted, String,
String, String]

Am I doing this wrong?

2016-01-25 7:30 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
> As discussed on IRC, your approach below looks right to me: dropWhile 
> (isLevityTy . idType) args. But you then said this wasn't working for you. 
> What does (map idType args) say?
>
> Richard
>
> On Jan 24, 2016, at 8:58 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:
>
>> Hi all,
>>
>> I'm looking for a reliable way of dropping levity args from TyCon 
>> applications.
>> When I know that a particular TyCon gets some number of levity args, I can 
>> just
>> drop the args manually (for example, I can drop the first half of arguments 
>> of
>> a tuple TyCon application) but the code looks fragile (what happens if I use 
>> a
>> different TyCon in the future) and confusing to the reader because it looks
>> like this:
>>
>>drop (length args `div` 2) args
>>
>> Ideally it'd look like this:
>>
>>dropWhile isLevityArg args
>>
>> Now, there's a function called isLevityTy, but I don't understand what it's
>> supposed to do. This doesn't do anyting to 'Boxed and 'Unboxed arguments:
>>
>>dropWhile (isLevityArg . idType) args
>>
>> Any ideas on this?
>>
>> Thanks..
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Adding a "release" setting in build.mk.sample (and some other build system questions)

2016-01-28 Thread Ömer Sinan Ağacan
I'm trying to figure out how to generate a release build. I thought it should
be "perf" setting, but then I realized ghc-stage1 is called with -O (instead of
-O2) when building stage2 with perf setting. So either perf is not the release
setting, or I need stage3 which is probably compiled with stage2 using -O2?

In any case, it'd be great to document this process of generating a release
build in build.mk.sample. If it's "perf" setting, then maybe we can rename it
to "release" or at least add a comment saying that that's the release build and
you should wait until stage3 is done.

Another thing that always confuses me is these settings:

SRC_HC_OPTS= -O -H64m
GhcStage1HcOpts= -O
GhcStage2HcOpts= -O2
GhcLibHcOpts   = -O2

As far as I can see, there's no documentation about these in the source tree. I
figured that `GhcStage1HcOpts` is passed to system GHC when compiling stage1,
and `GhcStage2Hcopts` is passed to ghc-stage1 when compiling stage 2. The lib
one is obvious, and it's passed to stage 1 as libs are built using stage 1. But
I still don't understand how is `SRC_HC_OPTS` is used, and what is used when
building stage 3.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: a reliable way of dropping levity args?

2016-01-28 Thread Ömer Sinan Ağacan
Ahh, levity is type of kinds, right? For some reason I thought kinds are now
levities (or whatever it's called). This makes sense. I just tried and I think
it works, thanks.

2016-01-28 19:39 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
>
> On Jan 28, 2016, at 5:48 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:
>>
>>| Just (tc, args) <- splitTyConApp_maybe ty
>>, isUnboxedTupleTyCon tc
>>= pprTrace "elimUbxSumRepTypes"
>>(text "orig args:" <+> ppr args $$
>> text "dropWhile isLevityTy args = " <+> ppr (dropWhile
>> isLevityTy args)) $
>>  concatMap go (drop (length args `div` 2) args)
>
> You want (dropWhile (isLevityTy . typeKind) args). isLevityTy simply checks 
> if its argument is exactly `Levity`.
>
> Does that work?
>
> Richard
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: a reliable way of dropping levity args?

2016-01-28 Thread Ömer Sinan Ağacan
It might be nice to actually replace `drop (length args `div` 2) args` with a
function `dropLevityArgs = dropWhile (isLevityTy . typeKind)` (I did this in my
branch). When I see a code that drops half of the type arguments it doesn't
make sense right away, but `dropLevityArgs` is at least giving an idea of
what's actually happening.

2016-01-28 20:30 GMT-05:00 Ömer Sinan Ağacan <omeraga...@gmail.com>:
> Ahh, levity is type of kinds, right? For some reason I thought kinds are now
> levities (or whatever it's called). This makes sense. I just tried and I think
> it works, thanks.
>
> 2016-01-28 19:39 GMT-05:00 Richard Eisenberg <e...@cis.upenn.edu>:
>>
>> On Jan 28, 2016, at 5:48 PM, Ömer Sinan Ağacan <omeraga...@gmail.com> wrote:
>>>
>>>| Just (tc, args) <- splitTyConApp_maybe ty
>>>, isUnboxedTupleTyCon tc
>>>= pprTrace "elimUbxSumRepTypes"
>>>(text "orig args:" <+> ppr args $$
>>> text "dropWhile isLevityTy args = " <+> ppr (dropWhile
>>> isLevityTy args)) $
>>>  concatMap go (drop (length args `div` 2) args)
>>
>> You want (dropWhile (isLevityTy . typeKind) args). isLevityTy simply checks 
>> if its argument is exactly `Levity`.
>>
>> Does that work?
>>
>> Richard
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


StgCase - are LiveVars and SRT fields going to be used?

2016-02-01 Thread Ömer Sinan Ağacan
Hi all,

This is how case expression in STG currently defined:


  | StgCase
(GenStgExpr bndr occ)
(GenStgLiveVars occ)
(GenStgLiveVars occ)
bndr
SRT
AltType
[GenStgAlt bndr occ]


The GenStgLiveVars and SRT fields are never used anywhere in the compiler
(except the printer). So the question is, I'm assuming those were used at some
point, but are they going to be used in the future? Or can I just delete those?

As a proof of concept, I just compiled GHC using this:


  | StgCase
(GenStgExpr bndr occ)
bndr
AltType
[GenStgAlt bndr occ]


Normally this is not a big deal, but I'm doing lots of STG-to-STG
transformations nowadays, and I have to keep those field updated which is
annoying as those are never going to be used (I can't even know if I'm doing it
right), or leave those `undefined` which is not a good practice.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: StgCase - are LiveVars and SRT fields going to be used?

2016-02-01 Thread Ömer Sinan Ağacan
https://phabricator.haskell.org/D1880

2016-02-01 18:04 GMT-05:00 Simon Peyton Jones :
> Those fields are dead, now that the Cmm pass deals with it.  We left it in 
> while making the transition, but they can go now.  Go ahead!
>
> (Lots of code should disappear along with them!)
>
> Simon
>
> | -Original Message-
> | From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ömer Sinan
> | Agacan
> | Sent: 01 February 2016 22:06
> | To: ghc-devs 
> | Subject: StgCase - are LiveVars and SRT fields going to be used?
> |
> | Hi all,
> |
> | This is how case expression in STG currently defined:
> |
> |
> |   | StgCase
> | (GenStgExpr bndr occ)
> | (GenStgLiveVars occ)
> | (GenStgLiveVars occ)
> | bndr
> | SRT
> | AltType
> | [GenStgAlt bndr occ]
> |
> |
> | The GenStgLiveVars and SRT fields are never used anywhere in the compiler
> | (except the printer). So the question is, I'm assuming those were used at
> | some
> | point, but are they going to be used in the future? Or can I just delete
> | those?
> |
> | As a proof of concept, I just compiled GHC using this:
> |
> |
> |   | StgCase
> | (GenStgExpr bndr occ)
> | bndr
> | AltType
> | [GenStgAlt bndr occ]
> |
> |
> | Normally this is not a big deal, but I'm doing lots of STG-to-STG
> | transformations nowadays, and I have to keep those field updated which is
> | annoying as those are never going to be used (I can't even know if I'm doing
> | it
> | right), or leave those `undefined` which is not a good practice.
> | ___
> | ghc-devs mailing list
> | ghc-devs@haskell.org
> | 
> https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.haskell.
> | org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
> | 
> devs=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7c12ca56c8fc514f477f7f08
> | 
> d32b53f4bc%7c72f988bf86f141af91ab2d7cd011db47%7c1=LPiupNbUJ9OGL9cmbP%2f
> | PAs2JSdxqlxk%2bGbXuYTHFbzg%3d
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


CoreLint check for case with no alts

2016-02-28 Thread Ömer Sinan Ağacan
Hi all,

CoreLint has a check that, when seeing a case expression with empty list of
alternatives, checks whether the scrutinee is bottom. This "bottom-ness" check
is, however, very simple and returning many false negatives. For example, when
it sees a case expression, all it does is:

go _ (Case _ _ _ alts)   = null alts

Which is just too simple for some cases. (it could check if all the RHSs are
bottom, or if the scrutinee is bottom etc.)

I guess this makes sense, since it's OK to generate unreachable code, but it's
not OK to not generate a code in a reachable path.

But in my case this is becoming problem as it's rejecting my seemingly
valid program. One of the relevant parts in my code is this:

case ww_s4C3 of ww_X4Fb {
  (#_||#) ww_s4Ce ->
case case ww_s4Ce of ww_s4F1 { (# ww_s4F2, ww_s4F3 #) ->
 lvl_s4F4 ww_s4F3 ww_s4F2
 }
of wild_00 {
  -- empty
};

lvl_s4F4 :: Int# -> String -> Var
[LclId, Arity=2, Str=DmdType (args: ) (res: x)]
lvl_s4F4 =
  \ (ww_s4F3 :: Int#) (ww_s4F2 :: String) ->
lvl_s3V4 (TyVar ww_s4F2 ww_s4F3)

lvl_s3V4 :: Var -> Var
[LclId, Arity=1, CallArity=1, Str=DmdType (args: ) (res: x)]
lvl_s3V4 = \ (i_a1vO :: Var) -> lvl_s4EZ i_a1vO

lvl_s4EZ :: Var -> Var
[LclId, Arity=1, Str=DmdType (args: ) (res: x)]
lvl_s4EZ = \ (i_a1vO :: Var) -> error ...

The scrutinee part of the case expression in the alternative is clearly bottom,
but this expression is rejected by the linter.

One easy solution is to implement a more precise test and use it in linter. But
I thought maybe the current implementation is deliberately so. Maybe the code
generator doesn't support that type of code etc. so I wanted to ask: Is there a
restriction on what kind empty case expressions are supported by the code
generator or can I just improve the lint check and assume that the code will be
handled by the code generator correctly?

Thanks.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Change in demand analysis results between 7.10.2 and RC1 (not fixed in RC2 and HEAD)

2016-02-28 Thread Ömer Sinan Ağacan
Thanks, but that patch looks like for CPR. In our case demands are
changed, so I don't see how that's related. Am I missing anything in
that patch?

2016-02-27 3:49 GMT-05:00 Joachim Breitner <m...@joachim-breitner.de>:
> Hi,
> Am Freitag, den 26.02.2016, 22:12 -0500 schrieb Ömer Sinan Ağacan:
>> While working on demand analyzer today we realized that there has
>> been some changes in demand analysis results between GHC 7.10.2 and
>> 8.0-rc2.
>
>
> a quick git log highlights this commit, as it relates to strict data
> constructors: 0696fc6d4de28cb589f6c751b8491911a5baf774
>
> commit 0696fc6d4de28cb589f6c751b8491911a5baf774
> Author: Simon Peyton Jones <simo...@microsoft.com>
> Date:   Fri Jun 26 11:40:01 2015 +0100
>
> Improve CPR behavior for strict constructors
>
> When working on Trac #10482 I noticed that we could give constructor
> arguments the CPR property if they are use strictly.
>
> This is documented carefully in
> Note [CPR in a product case alternative]
> and also
> Note [Initial CPR for strict binders]
>
> There are a bunch of intersting examples in
> Note [CPR examples]
> which I have added to the test suite as T10482a.
>
> I also added a test for #10482 itself.
>
> I did not investigate whether this could actually have effected¹ this
> change.
>
> Greetings,
> Joachim
>
> ¹ How do you recognize a regular xkcd reader?
>   He uses effect as an verb. https://xkcd.com/326/
>
> --
> --
> Joachim “nomeata” Breitner
>   m...@joachim-breitner.de • https://www.joachim-breitner.de/
>   XMPP: nome...@joachim-breitner.de • OpenPGP-Key: 0xF0FBF51F
>   Debian Developer: nome...@debian.org
>
>
> ___
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Change in demand analysis results between 7.10.2 and RC1 (not fixed in RC2 and HEAD)

2016-02-29 Thread Ömer Sinan Ağacan
> Why do you say
>
> |  In our case, we prefer the result in 7.10.2 of course, because that's a
> |  more precise demand and it gives us more opportunities for
> |  optimizations. But I guess this could potentially reveal itself in some
>
> What optimisations do you have in mind?

I just had worker/wrapper in mind. I just realized that <L,A> is actually a
very good demand for W/W, so this new demand is actually better. I was thinking
naively that more strict is better, ignoring the cardinality analysis parts and
redundant argument passing.

2016-02-29 5:10 GMT-05:00 Simon Peyton Jones <simo...@microsoft.com>:
> See Note [Add demands for strict constructors] in DmdAnal, esp the bit that 
> says
> If the argument is not used at all in the alternative (i.e. it is
> Absent), then *don't* add a 'seqDmd'.  If we do, it makes it look used
> and hence it'll be passed to the worker when it doesn't need to be.
> Hence the isAbsDmd test in addDataConStrictness.
>
> Why do you say
>
> |  In our case, we prefer the result in 7.10.2 of course, because that's a
> |  more precise demand and it gives us more opportunities for
> |  optimizations. But I guess this could potentially reveal itself in some
>
> What optimisations do you have in mind?
>
> Simon
>
> |  -Original Message-
> |  From: Ömer Sinan Ağacan [mailto:omeraga...@gmail.com]
> |  Sent: 27 February 2016 03:13
> |  To: ghc-devs <ghc-devs@haskell.org>; Simon Peyton Jones
> |  <simo...@microsoft.com>
> |  Cc: Jose Calderon <j...@jmct.cc>
> |  Subject: Change in demand analysis results between 7.10.2 and RC1 (not
> |  fixed in RC2 and HEAD)
> |
> |  Hi all,
> |
> |  While working on demand analyzer today we realized that there has been
> |  some changes in demand analysis results between GHC 7.10.2 and 8.0-rc2.
> |  Here's a minimal example:
> |
> |  {-# LANGUAGE BangPatterns #-}
> |
> |  module Main where
> |
> |  data Prod a = Prod !a !a
> |
> |  addProd :: Prod Int -> Prod Int -> Prod Int
> |  addProd (Prod i1 i2) (Prod i3 i4) = Prod i1 (i2 + i4)
> |
> |  main = return ()
> |
> |  Compiled with 7.10.2:
> |
> |  addProd :: Prod Int -> Prod Int -> Prod Int
> |  [GblId,
> |   Arity=2,
> |   Caf=NoCafRefs,
> |   Str=DmdType <S(SS),1*U(U,U(U))><S(SS),1*U(1*H,U(U))>m,
> |   ...]
> |  addProd =
> |\ (ds_dzH :: Prod Int) (ds1_dzI :: Prod Int) ->
> |  case ds_dzH of _ [Occ=Dead] { Prod i1_an2 i2_an3 ->
> |  case i2_an3 of _ [Occ=Dead] { GHC.Types.I# x_s2B4 ->
> |  case ds1_dzI of _ [Occ=Dead] { Prod i3_an4 i4_an5 ->
> |  case i4_an5 of _ [Occ=Dead] { GHC.Types.I# y_s2B7 ->
> |
> |  https://na01.safelinks.protection.outlook.com/?url=Main.Prod=01%7c
> |  01%7csimonpj%40064d.mgd.microsoft.com%7c7b5d6e60d31348506eb108d33f23f6b
> |  f%7c72f988bf86f141af91ab2d7cd011db47%7c1=NfCiyeSjPwsWage0KlgkMkQR
> |  jWVexsdlCq0Dla%2f1I10%3d @ Int i1_an2 (GHC.Types.I# (GHC.Prim.+# x_s2B4
> |  y_s2B7))
> |  }
> |  }
> |  }
> |  }
> |
> |  Compiled with 8.0-rc2:
> |
> |  -- RHS size: {terms: 20, types: 17, coercions: 0}
> |  addProd :: Prod Int -> Prod Int -> Prod Int
> |  [GblId,
> |   Arity=2,
> |   Caf=NoCafRefs,
> |   Str=DmdType <S(SS),1*U(U,U(U))><S(LS),1*U(A,U(U))>m,
> |   ...]
> |  addProd =
> |\ (ds_dQL :: Prod Int) (ds1_dQM :: Prod Int) ->
> |  case ds_dQL of _ [Occ=Dead] { Prod i1_avS i2_avT ->
> |  case i2_avT of _ [Occ=Dead] { GHC.Types.I# x_s1vO ->
> |  case ds1_dQM of _ [Occ=Dead] { Prod i3_avU i4_avV ->
> |  case i4_avV of _ [Occ=Dead] { GHC.Types.I# y_s1vR ->
> |
> |  https://na01.safelinks.protection.outlook.com/?url=Main.Prod=01%7c
> |  01%7csimonpj%40064d.mgd.microsoft.com%7c7b5d6e60d31348506eb108d33f23f6b
> |  f%7c72f988bf86f141af91ab2d7cd011db47%7c1=NfCiyeSjPwsWage0KlgkMkQR
> |  jWVexsdlCq0Dla%2f1I10%3d @ Int i1_avS (GHC.Types.I# (GHC.Prim.+# x_s1vO
> |  y_s1vR))
> |  }
> |  }
> |  }
> |  }
> |
> |  To highlight the difference,
> |
> |  GHC 7.10.2:  <S(SS),1*U(U,U(U))><S(SS),1*U(1*H,U(U))>
> |  GHC 8.0-rc2: <S(SS),1*U(U,U(U))><S(LS),1*U(A,U(U))>
> |
> |  (NOTE: Also tried with HEAD and rc1 just now, the results are the same
> |  as rc2)
> |
> |  The demand put on the second argument is more strict in GHC 7.10. Was
> |  that an intentional change? Any ideas on why this might be happening?
> |
> |  In our case, we prefer the result in 7.10.2 of course, because that's a
> |  more precise demand and it gives us more opportunities for
> |  optimizations. But I guess this could potentially reveal itself in some
> |  other situations and make some programs slower? Any ideas?
> |
> |  Thanks..
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: CoreLint check for case with no alts

2016-02-29 Thread Ömer Sinan Ağacan
> So feel free to make Lint cleverer; make sure you add a Note.  But if it
> /needs/ to be cleverer, that suggests that the simplifier should be cleverer
> instead, and should simplify the code so that even a dumb Core Lint has no
> trouble.

Good point. The problem is linter is checking every intermediate Core, and
apparently not all Core passes are that smart about simplifications.

> In your example why didn't the simplifier do case-of-case?

This code is generated by floatIn (FloatInwards).


One more question. Do you think this is a safe change in coreToStgExpr that
handles empty cases:

coreToStgExpr (Case scrut bndr ty [])
  = coreToStgExpr (Case scrut bndr ty [(DEFAULT, [], mkImpossibleExpr ty)])

When I make this change some programs are failing with this:

Oops!  Entered absent arg w_sc1l FilePath

But that may be because of some libraries I need to recompile, although I'm not
sure why this would be the case.

The problem I'm trying to solve is my lint-safe (after the smarter lint check
about bottoming expressions) programs are failing with segfaults. Of course
that may be because I'm doing something wrong in STG level, but I'm trying to
make sure everything above STG is correct and bug-free. It'd be really great if
I could somehow generate an erroring expression in some places that are
supposed to be unreachable, just to make sure my segfaults are not related with
those.

2016-02-29 6:32 GMT-05:00 Simon Peyton Jones :
> |  I wanted to ask: Is there a restriction on what kind empty case
> |  expressions are supported by the code generator or can I just improve
> |  the lint check and assume that the code will be handled by the code
> |  generator correctly?
>
> I believe the latter.  See CoreToStg line 364.
>
> So feel free to make Lint cleverer; make sure you add a Note.  But if it 
> /needs/ to be cleverer, that suggests that the simplifier should be cleverer 
> instead, and should simplify the code so that even a dumb Core Lint has no 
> trouble.
>
> In your example why didn't the simplifier do case-of-case?
>
> I suppose that this might be after some pass and before a simplifier run.
>
> Simon
>
> |  -Original Message-
> |  From: ghc-devs [mailto:ghc-devs-boun...@haskell.org] On Behalf Of Ömer
> |  Sinan Agacan
> |  Sent: 29 February 2016 03:16
> |  To: ghc-devs 
> |  Subject: CoreLint check for case with no alts
> |
> |  Hi all,
> |
> |  CoreLint has a check that, when seeing a case expression with empty
> |  list of alternatives, checks whether the scrutinee is bottom. This
> |  "bottom-ness" check is, however, very simple and returning many false
> |  negatives. For example, when it sees a case expression, all it does is:
> |
> |  go _ (Case _ _ _ alts)   = null alts
> |
> |  Which is just too simple for some cases. (it could check if all the
> |  RHSs are bottom, or if the scrutinee is bottom etc.)
> |
> |  I guess this makes sense, since it's OK to generate unreachable code,
> |  but it's not OK to not generate a code in a reachable path.
> |
> |  But in my case this is becoming problem as it's rejecting my seemingly
> |  valid program. One of the relevant parts in my code is this:
> |
> |  case ww_s4C3 of ww_X4Fb {
> |(#_||#) ww_s4Ce ->
> |  case case ww_s4Ce of ww_s4F1 { (# ww_s4F2, ww_s4F3 #) ->
> |   lvl_s4F4 ww_s4F3 ww_s4F2
> |   }
> |  of wild_00 {
> |-- empty
> |  };
> |
> |  lvl_s4F4 :: Int# -> String -> Var
> |  [LclId, Arity=2, Str=DmdType (args: ) (res: x)]
> |  lvl_s4F4 =
> |\ (ww_s4F3 :: Int#) (ww_s4F2 :: String) ->
> |  lvl_s3V4 (TyVar ww_s4F2 ww_s4F3)
> |
> |  lvl_s3V4 :: Var -> Var
> |  [LclId, Arity=1, CallArity=1, Str=DmdType (args: ) (res: x)]
> |  lvl_s3V4 = \ (i_a1vO :: Var) -> lvl_s4EZ i_a1vO
> |
> |  lvl_s4EZ :: Var -> Var
> |  [LclId, Arity=1, Str=DmdType (args: ) (res: x)]
> |  lvl_s4EZ = \ (i_a1vO :: Var) -> error ...
> |
> |  The scrutinee part of the case expression in the alternative is clearly
> |  bottom, but this expression is rejected by the linter.
> |
> |  One easy solution is to implement a more precise test and use it in
> |  linter. But I thought maybe the current implementation is deliberately
> |  so. Maybe the code generator doesn't support that type of code etc. so
> |  I wanted to ask: Is there a restriction on what kind empty case
> |  expressions are supported by the code generator or can I just improve
> |  the lint check and assume that the code will be handled by the code
> |  generator correctly?
> |
> |  Thanks.
> |  ___
> |  ghc-devs mailing list
> |  ghc-devs@haskell.org
> |  https://na01.safelinks.protection.outlook.com/?url=http%3a%2f%2fmail.ha
> |  skell.org%2fcgi-bin%2fmailman%2flistinfo%2fghc-
> |  devs=01%7c01%7csimonpj%40064d.mgd.microsoft.com%7ce621b9bcb2774ff8
> |  

Change in demand analysis results between 7.10.2 and RC1 (not fixed in RC2 and HEAD)

2016-02-26 Thread Ömer Sinan Ağacan
Hi all,

While working on demand analyzer today we realized that there has been some
changes in demand analysis results between GHC 7.10.2 and 8.0-rc2. Here's a
minimal example:

{-# LANGUAGE BangPatterns #-}

module Main where

data Prod a = Prod !a !a

addProd :: Prod Int -> Prod Int -> Prod Int
addProd (Prod i1 i2) (Prod i3 i4) = Prod i1 (i2 + i4)

main = return ()

Compiled with 7.10.2:

addProd :: Prod Int -> Prod Int -> Prod Int
[GblId,
 Arity=2,
 Caf=NoCafRefs,
 Str=DmdType m,
 ...]
addProd =
  \ (ds_dzH :: Prod Int) (ds1_dzI :: Prod Int) ->
case ds_dzH of _ [Occ=Dead] { Prod i1_an2 i2_an3 ->
case i2_an3 of _ [Occ=Dead] { GHC.Types.I# x_s2B4 ->
case ds1_dzI of _ [Occ=Dead] { Prod i3_an4 i4_an5 ->
case i4_an5 of _ [Occ=Dead] { GHC.Types.I# y_s2B7 ->
Main.Prod @ Int i1_an2 (GHC.Types.I# (GHC.Prim.+# x_s2B4 y_s2B7))
}
}
}
}

Compiled with 8.0-rc2:

-- RHS size: {terms: 20, types: 17, coercions: 0}
addProd :: Prod Int -> Prod Int -> Prod Int
[GblId,
 Arity=2,
 Caf=NoCafRefs,
 Str=DmdType m,
 ...]
addProd =
  \ (ds_dQL :: Prod Int) (ds1_dQM :: Prod Int) ->
case ds_dQL of _ [Occ=Dead] { Prod i1_avS i2_avT ->
case i2_avT of _ [Occ=Dead] { GHC.Types.I# x_s1vO ->
case ds1_dQM of _ [Occ=Dead] { Prod i3_avU i4_avV ->
case i4_avV of _ [Occ=Dead] { GHC.Types.I# y_s1vR ->
Main.Prod @ Int i1_avS (GHC.Types.I# (GHC.Prim.+# x_s1vO y_s1vR))
}
}
}
}

To highlight the difference,

GHC 7.10.2:  
GHC 8.0-rc2: 

(NOTE: Also tried with HEAD and rc1 just now, the results are the same as rc2)

The demand put on the second argument is more strict in GHC 7.10. Was that an
intentional change? Any ideas on why this might be happening?

In our case, we prefer the result in 7.10.2 of course, because that's a more
precise demand and it gives us more opportunities for optimizations. But I
guess this could potentially reveal itself in some other situations and make
some programs slower? Any ideas?

Thanks..
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


  1   2   3   4   >