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?

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...)

Re: Do we need to maintain PrimRep.VecRep?

2016-06-07 Thread Ömer Sinan Ağacan
ing > 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 >

Re: Do we need to maintain PrimRep.VecRep?

2016-06-07 Thread Ömer Sinan Ağacan
ecRep'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 >&g

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

Re: Parser changes for supporting top-level SCC annotations

2016-06-01 Thread Ömer Sinan Ağacan
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

Re: Core of a whole package

2016-06-01 Thread Ömer Sinan Ağacan
ion 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, Ju

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

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

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

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.

Re: comment lines in Cmm outputs

2016-05-29 Thread Ömer Sinan Ağacan
t;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 usef

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

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

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-stag

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

Re: Initial compile time benchmarks

2016-03-31 Thread Ömer Sinan Ağacan
better job probably. One last thing is that profiling can prevent some optimizations and cause different runtime behavior. Problems with instrumentation ... 2016-03-31 12:01 GMT-04:00 Ömer Sinan Ağacan <omeraga...@gmail.com>: > Forgot to mention that I use `cabal install > --g

Re: Initial compile time benchmarks

2016-03-31 Thread Ömer Sinan Ağacan
Hi Joachim, That's GHC HEAD at the time with -O1 for stage 2 + libs. The way I generate the logs is: - I create a cabal sandbox and run `cabal exec zsh` to set up the env variables. - I install packages in that shell. - $ (cat .cabal-sandbox/logs/*.log | analyze-ghc-timings) > output I

Re: Initial compile time benchmarks

2016-03-31 Thread Ömer Sinan Ağacan
Forgot to mention that I use `cabal install --ghc-options="-v3" -v3` to install the packages. 2016-03-31 12:00 GMT-04:00 Ömer Sinan Ağacan <omeraga...@gmail.com>: > Hi Joachim, > > That's GHC HEAD at the time with -O1 for stage 2 + libs. > > The way I generate the

Initial compile time benchmarks

2016-03-29 Thread Ömer Sinan Ağacan
Hi all, Using Ben's timing patch [^1], Cabal, and a Haskell program to parse generated logs [^2], I generated some tables that show compile times of modules in hxt, haskell-src-exts, lens, and all of their dependencies:

Re: Disappearing case alternative?

2016-03-11 Thread Ömer Sinan Ağacan
Empty case expressions like `case evalP @ (Pair Int) ds of wild { }` are only valid if the scrutinee is bottom, see CoreLint.hs for how exprIsBottom is used and CoreUtils.hs for how it's defined. So it seems like the simplifier somehow figured that `evalP @ (Pair Int) ds` is bottom, and generated

Re: 'lub' and 'both' on strictness - what does it mean for products to have different arity?

2016-03-04 Thread Ömer Sinan Ağacan
ll the cases for UCall, and so on. That way I know I've > got coverage. > > (And perhaps it's more efficient: we pattern match at most once on each > argument. > > Simon > > | > | I didn't check all the cases to see if it's really commutative or not, > | but c

Re: 'lub' and 'both' on strictness - what does it mean for products to have different arity?

2016-03-01 Thread Ömer Sinan Ağacan
the cases to see if it's really commutative or not, but can I assume that they need to be commutative and simplify the code? Otherwise let's add a note about why they're not commutative? Thanks.. 2016-03-02 1:07 GMT-05:00 Ömer Sinan Ağacan <omeraga...@gmail.com>: >> Could I ask

Re: 'lub' and 'both' on strictness - what does it mean for products to have different arity?

2016-03-01 Thread Ömer Sinan Ağacan
> Could I ask that you add this example as a Note to the relevant functions, so > that the next time someone asks this question they'll find the answer right > there? Yep, I'll do that soon. 2016-03-01 12:01 GMT-05:00 Simon Peyton Jones : > Omer > > Joachim is right. The

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
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: 2

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

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

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 _

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

'lub' and 'both' on strictness - what does it mean for products to have different arity?

2016-02-19 Thread Ömer Sinan Ağacan
I was looking at implementations of LUB and AND on demand signatures and I found this interesting case: lubStr (SProd s1) (SProd s2) | length s1 == length s2 = mkSProd (zipWith lubArgStr s1 s2) | otherwise= HeadStr The "otherwise" case is interesting, I'd

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 defa

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

2016-02-05 Thread Ömer Sinan Ağacan
rstand 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 <om

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

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

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

Re: a reliable way of dropping levity args?

2016-01-28 Thread Ömer Sinan Ağacan
asn'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 >> app

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

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

Re: a reliable way of dropping levity args?

2016-01-28 Thread Ömer Sinan Ağacan
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, than

a reliable way of dropping levity args?

2016-01-24 Thread Ömer Sinan Ağacan
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

Fixing #11444 - OK-for-speculation check rejects valid program?

2016-01-19 Thread Ömer Sinan Ağacan
I found one of the problems with #11444, but I don't know how to fix it. The problem is that the desugarer is generating this function: ptrEq [InlPrag=NOINLINE] :: forall a_a1wc. a_a1wc -> a_a1wc -> Bool [LclIdX, Str=DmdType] ptrEq = \ (@ a_a1Ts) (x_a1we :: a_a1Ts) (y_a1wf ::

Re: How to build profiled stage1?

2016-01-19 Thread Ömer Sinan Ağacan
An update: If I just clone from scratch, set the flavor "prof" and run make, it doesn't work. But this is another problem, my original problem is about building profiling stage1, rather than stage2. 2016-01-18 15:10 GMT-05:00 Ömer Sinan Ağacan <omeraga...@gmail.com>: > I'm

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

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,

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

Re: Implementation idea for unboxed polymorphic types

2016-01-05 Thread Ömer Sinan Ağacan
.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`

Re: Kinds of type synonym arguments

2015-12-20 Thread Ömer Sinan Ağacan
f 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 Sin

Re: Kinds of type synonym arguments

2015-12-16 Thread Ömer Sinan Ağacan
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-triv

Re: Kinds of type synonym arguments

2015-12-15 Thread Ömer Sinan Ağacan
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 >&

Re: Kinds of type synonym arguments

2015-12-15 Thread Ömer Sinan Ağacan
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 > |

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 ...

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

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

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

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 {

-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

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

2015-12-07 Thread Ömer Sinan Ağacan
u 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: >>

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

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

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

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

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

Re: Implementation idea for unboxed polymorphic types

2015-11-16 Thread Ömer Sinan Ağacan
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 th

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

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,

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! > >

Re: How inline pragma works

2015-11-10 Thread Ömer Sinan Ağacan
> > --- > С уважением, > Жаворонков Эдгар > > 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/late

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

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

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

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

Re: is this change in TH error message intentional?

2015-10-20 Thread Ömer Sinan Ağacan
n.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 o

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

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

Re: Show instances for GHC internals

2015-10-20 Thread Ömer Sinan Ağacan
ction 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 >> unsafeInt

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)

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

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

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

Re: question about GHC API on GHC plugin

2015-09-04 Thread Ömer Sinan Ağacan
thing, 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

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

Re: question about GHC API on GHC plugin

2015-08-25 Thread Ömer Sinan Ağacan
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

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

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

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

2015-08-22 Thread Ömer Sinan Ağacan
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

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'

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

Re: expanding type synonyms in error messages

2015-06-26 Thread Ömer Sinan Ağacan
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

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

Re: expanding type synonyms in error messages

2015-06-19 Thread Ömer Sinan Ağacan
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

Re: expanding type synonyms in error messages

2015-06-19 Thread Ömer Sinan Ağacan
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

Re: expanding type synonyms in error messages

2015-06-18 Thread Ömer Sinan Ağacan
), 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

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

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

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

2014-10-02 Thread Ömer Sinan Ağacan
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

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

2014-09-30 Thread Ömer Sinan Ağacan
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: 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

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

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

2014-08-13 Thread Ömer Sinan Ağacan
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

biographical profiling is broken?

2014-08-07 Thread Ömer Sinan Ağacan
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

<    1   2   3   4   >