Loading a typechecked module and then using it immediately as a package

2021-06-25 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I have the following to .hs files: 1. MyLib.hs: module MyLib where ... 2. Test.hs: {-# LANGUAGE PackageImports #-} module Test where import "my-pkg" MyLib ... I would like to parse/typecheck/load MyLib.hs into some Unit "my-unit", then add that to the package "my-pkg", an

RE: [External] Re: Loading a typechecked module and then using it immediately as a package

2021-06-27 Thread Erdi, Gergo via ghc-devs
github.com%2Fmpickering%2F5029c7f244c484c91d665bcbc6bc6406 Cheers, Matt On Fri, Jun 25, 2021 at 10:20 AM Erdi, Gergo via ghc-devs wrote: > > PUBLIC > > > Hi, > > > > I have the following to .hs files: > > > > MyLib.hs: > > module MyLib where > … >

RE: [External] Re: Loading a typechecked module and then using it immediately as a package

2021-06-28 Thread Erdi, Gergo via ghc-devs
hing button in Outlook to protect the Bank and our clients. Hi Gergo, Please see a minimal example in this gist. https://clicktime.symantec.com/3Eb2qXqu8Yp6VtdK9d5pNmL7Vc?u=https%3A%2F%2Fgist.github.com%2Fmpickering%2F5029c7f244c484c91d665bcbc6bc6406 Cheers, Matt On Fri, Jun 25, 2021 at 10:

Re: Loading a typechecked module and then using it immediately as a package

2021-06-29 Thread Erdi, Gergo via ghc-devs
9d5pNmL7Vc?u=https%3A%2F%2Fgist.github.com%2Fmpickering%2F5029c7f244c484c91d665bcbc6bc6406 Cheers, Matt On Fri, Jun 25, 2021 at 10:20 AM Erdi, Gergo via ghc-devs wrote: > > PUBLIC > > > Hi, > > > > I have the following to .hs files: > > > > MyLib.hs: > > module My

RE: Loading a typechecked module and then using it immediately as a package

2021-06-29 Thread Erdi, Gergo via ghc-devs
PUBLIC I don't know yet what's going on, but one thing I did notice is that `findInstalledHomeModule` returns `InstalledFound` for `MyLib`, which doesn't sound right to me -- `MyLib` should come from the "fake-uid" unit, and `Test` is typechecked in the `mainUnitId`. -Original Message-

Re: Loading a typechecked module and then using it immediately as a package

2021-06-29 Thread Erdi, Gergo via ghc-devs
PUBLIC Should I? OK, I just tried calling `flushFinderCaches` after I change the home unit to `mainUnitId`, but I still get exactly the same behaviour: `findInstalledHomeModule` returns `InstalledFound` and things go downhill from there. -Original Message- From: Matthew Pickering Sen

Re: Loading a typechecked module and then using it immediately as a package

2021-07-01 Thread Erdi, Gergo via ghc-devs
PUBLIC Unfortunately, that would take quite some extra effort. However, I think I have figured this out in the meantime: it seems it wasn't the FinderCache that needed invalidating, but the ModuleGraph. So now I have the following code for changing the home unit: ``` setHomeUnit :: (GhcMonad m

Marking ParsedModule fragments as non-user-originating

2021-07-06 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I'd like to hijack some syntax (like string literals or list patterns) for my own use, and I thought a low-tech way of doing that is to transform the ParsedModule before typechecking. For example, if I have a function `uncons :: Array a -> Maybe (a, Array a)`, I can rewrite the patt

RE: Marking ParsedModule fragments as non-user-originating

2021-07-06 Thread Erdi, Gergo via ghc-devs
lugin. Simon From: ghc-devs mailto:ghc-devs-boun...@haskell.org>> On Behalf Of Erdi, Gergo via ghc-devs Sent: 06 July 2021 09:08 To: ghc-devs@haskell.org<mailto:ghc-devs@haskell.org> Subject: Marking ParsedModule fragments as non-user-originating PUBLIC Hi, I'd like to hijac

Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating)

2021-07-12 Thread Erdi, Gergo via ghc-devs
ename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in your plugin. Simon From: ghc-devs mailto:ghc-devs-boun...@haskell.org>> On Behalf Of Erdi, Gergo

RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating)

2021-07-12 Thread Erdi, Gergo via ghc-devs
rloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does something similar to what you want. Maybe you can use the same mechanism in

RE: Using overloaded syntax to avoid `base` dependency (RE: Marking ParsedModule fragments as non-user-originating)

2021-07-12 Thread Erdi, Gergo via ghc-devs
g (badViewPat p) } More generally, don't you just want OverloadedStrings or OverloadedLists? You might want to read Note [Handling overloaded and rebindable constructs] in GHC.Rename.Expr, and Note [Rebindable syntax and HsExpansion] in GCH.Hs.Expr. These Notes describe how GHC already does som

mkIfaceTc panics with "lookupVers1"

2021-07-13 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I'm trying to use `mkIfaceTc` to make a ModIface from the results of typechecking. Everything goes well until it gets to `makeFullIface`, where it fails to find some imported fingerprints: hello: hello: panic! (the 'impossible' happened) (GHC version 9.0.1: lookupVers1 My

Where else do I need to register fixity declarations?

2021-07-27 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, In the attached program, I am typechecking two Haskell modules with GHC 9.0.1: `Imported.hs` defines some infix operators, and `Importer.hs` uses them. After typechecking the first one, I put it in the moduleNameProvidersMap and the HPT. However, when I am typechecking the second on

Where (else) do I need to register instances from loaded modules?

2021-08-23 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I am trying to typecheck & load three modules using the GHC API. The first one defines a class, the second one defines an instance of said class, and the third one uses the instance (attached as Class.src, Instance.src and Use.src, respectively). The problem is that when I typecheck

Re: Where (else) do I need to register instances from loaded modules?

2021-08-24 Thread Erdi, Gergo via ghc-devs
INTERNAL Hi, Thanks Matt! Unfortunately, I couldn't get it working even with these suggestions. 1. I changed registerModule so that it only changes the HPT when toUnitId (moduleUnit mod) == homeUnitId (hsc_dflags env). But I'm pretty sure this will be vacuously true, since the unit of the mod

RE: Where (else) do I need to register instances from loaded modules?

2021-08-24 Thread Erdi, Gergo via ghc-devs
INTERNAL Oops, forgot to attach the updated program -Original Message- From: Erdi, Gergo Sent: Wednesday, August 25, 2021 10:37 AM To: Matthew Pickering Cc: GHC ; ge...@erdi.hu; Montelatici, Raphael Laurent Subject: Re: Where (else) do I need to register instances from loaded modules?

Registering orphan instances and filling the `deps` field of ModIface [RE: Where (else) do I need to register instances from loaded modules?]

2021-08-26 Thread Erdi, Gergo via ghc-devs
PUBLIC Re: #1., I've simplified the code by removing all the Unit shuffling: everything is now in mainUnit. Unfortunately, this doesn't change anything other than cutting a cool 100 lines from the MWE code; I'm attaching the new smaller & simpler version. It is based on GHC 9.0.1 with an extra

Inter-module inlining doesn't work, Id unfolding seems to be empty -- why?

2021-09-01 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, The attached program uses the GHC 9.0.1 API to typecheck and compile a single module that contains a single definition marked as INLINE: module Inline where data A = A1 | A2 data B = B1 | B2 {-# INLINE f #-} f :: A ->B f A1 = B1 f A2 = B2 In my bigger program, I noticed that usage

RE: Inter-module inlining doesn't work, Id unfolding seems to be empty -- why?

2021-09-01 Thread Erdi, Gergo via ghc-devs
PUBLIC Never mind, turns out this was because OmitInterfacePragmas is turned on by default... (why?). After unsetting OmitInterfacePragmas in the dflags, I get the expected unfolding, and inter-module inlining works. Unf{Src=InlineStable, TopLvl=True, Value=True, ConLike=True, WorkFree=True

Re: Registering orphan instances and filling the `deps` field of ModIface [RE: Where (else) do I need to register instances from loaded modules?]

2021-09-08 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, Any other ideas I could try? Gergo -Original Message- From: Erdi, Gergo Sent: Friday, August 27, 2021 2:42 PM To: 'Matthew Pickering' Cc: 'GHC' ; 'ge...@erdi.hu' ; Montelatici, Raphael Laurent Subject: Registering orphan instances and filling the `deps` field of ModIface

SOLVED: Registering orphan instances and filling the `deps` field of ModIface [RE: Where (else) do I need to register instances from loaded modules?]

2021-09-27 Thread Erdi, Gergo via ghc-devs
PUBLIC So these orphans got less loving attention on the mailing list than Oliver Twist, but I ended up solving this so just in case anyone else runs into this, here's what was going wrong. It turns out the key to everything was this: > 2. I also changed mkModIface [...] by copy-pasting more c

Instantiation of overloaded definition *in Core*

2021-10-04 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I'd like to instantiate Core definitions. For example, suppose I have the following Core definition: foo :: forall m a b. Monad m => m a -> m b -> m b foo = \ @m ($d :: Monad m) @a @b (ma :: m a) (mb :: m b) -> ... Now let's say I'd like to instantiate it for m ~ IO. It is quite st

Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-05 Thread Erdi, Gergo via ghc-devs
ave a simple API to do that, although it would not be hard to create one. Simon PS: I am leaving Microsoft at the end of November 2021, at which point simo...@microsoft.com<mailto:simo...@microsoft.com> will cease to work. Use simon.peytonjo...@gmail.com<mailto:simon.peytonjo...@gmail.

Re: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-06 Thread Erdi, Gergo via ghc-devs
INTERNAL I see. That will be a bit more involved to try out, because I don't have a ModGuts at hand -- I only have the ModDetails, and the collected CoreProgram from the whole program. But it seems `specProgram` only really uses the rules and the binds from the `ModGuts`, so I should be all rig

RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-06 Thread Erdi, Gergo via ghc-devs
PUBLIC PUBLIC Indeed, I am using 9.0.1. I'll try upgrading. Thanks! From: Simon Peyton Jones Sent: Wednesday, October 6, 2021 6:12 PM To: Erdi, Gergo Cc: Montelatici, Raphael Laurent ; GHC Subject: [External] RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *

RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-10 Thread Erdi, Gergo via ghc-devs
PUBLIC PUBLIC Hi Simon, Matt & others, It took me until now to be able to try out GHC HEAD, mostly because I had to adapt to all the GHC.Unit.* refactorings. However, now I am on a466b02492f73a43c6cb9ce69491fc85234b9559 which includes the commit Simon pointed out. My original plan was to exp

-O* does more than what's in optLevelFlags?

2021-10-10 Thread Erdi, Gergo via ghc-devs
PUBLIC What is set by -O* that is not included in optLevelFlags? I would have thought that setting all the flags implied by, e.g., -O1, would be the same as setting -O1 itself. But this is not the case! Here are all the flags for O1 from optLevelFlags: Opt_DoLambdaEtaExpansion Opt_DoEtaReducti

RE: -O* does more than what's in optLevelFlags?

2021-10-11 Thread Erdi, Gergo via ghc-devs
PUBLIC I've done some digging into this, and it turns out the DynFlag's `optLevel` itself is used at some places, most notably when creating the main [CoreToDo]. So turning on all these flags on their own doesn't equal setting -On for the right "n"; in fact, currently setting most of these flag

RE: Specialisation doesn't kick in (RE: Instantiation of overloaded definition *in Core*)

2021-10-11 Thread Erdi, Gergo via ghc-devs
PUBLIC PUBLIC Trust me when I say I understand your frustration. It is even more frustrating for me not to be able to just send a Github repo link containing my code... I'll try to make an MWE that demonstrates the problem but it will probably take quite some time. I was hoping that maybe the

RE: -O* does more than what's in optLevelFlags?

2021-10-11 Thread Erdi, Gergo via ghc-devs
to:simon.peytonjo...@gmail.com> instead. (For now, it just forwards to simo...@microsoft.com<mailto:simo...@microsoft.com>.) From: ghc-devs mailto:ghc-devs-boun...@haskell.org>> On Behalf Of Erdi, Gergo via ghc-devs Sent: 11 October 2021 08:54 To: 'GHC' mailto:

RE: -O* does more than what's in optLevelFlags?

2021-10-11 Thread Erdi, Gergo via ghc-devs
r 2021, at which point simo...@microsoft.com<mailto:simo...@microsoft.com> will cease to work. Use simon.peytonjo...@gmail.com<mailto:simon.peytonjo...@gmail.com> instead. (For now, it just forwards to simo...@microsoft.com<mailto:simo...@microsoft.com>.) From: ghc-devs mailto:ghc-de

RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

2021-10-14 Thread Erdi, Gergo via ghc-devs
PUBLIC PUBLIC OK I now have a standalone demonstrator that shows, at least, that the default method implementation is not specialized. With the attached input programs, the resulting Core (using GHC e46edfcf47d674731935b2ea1443cc7927e071fb) is as follows (only showing the relevant parts): se

RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

2021-10-18 Thread Erdi, Gergo via ghc-devs
PUBLIC PUBLIC Thanks for looking into this! `Paths_ghc_lib` is referenced just because I am using GHC via ghc-lib. You can of course instead use a local full build of GHC for the libDir. Please find an updated version attached that does that – you’ll just have to adapt the definition of `lib

RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

2021-10-19 Thread Erdi, Gergo via ghc-devs
PUBLIC PUBLIC Do you have a full GHC build there? Are you using Hadrian? Did you set `libDir`’s definition in the source file to where you have GHC built? I just tried, and if I remove the files from my GHC build, I am able to rebuild them: mi@localhost[ghc] $ for i in settings llvm-passes ll

RE: Specialisation doesn't kick in -- NOW WITH MINIMAL WORKING EXAMPLE (RE: Instantiation of overloaded definition *in Core*)

2021-10-19 Thread Erdi, Gergo via ghc-devs
PUBLIC PUBLIC “settings”? Honestly, I have no idea. GHC looks at these files in the directory passed to runGhc, and in my local setup I have some convoluted ghc-lib-based system to persist these files and also the base package.db into a Stack/cabal-installable package, but these are only need

Recognizing default method implementations

2021-11-30 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, Is there a way to recognize that an Id / Var refers to a default method implementation, e.g. $dm/= in the following? $dm/= :: forall a. Eq a => a -> a -> Bool [GblId, Arity=3, Unf=OtherCon []] $dm/= = \ (@a_ahz) ($dEq_sI6 [Occ=Once1] :: Eq a_ahz) (x_sI7 [Occ=Once1] :: a

RE: Recognizing default method implementations

2021-12-01 Thread Erdi, Gergo via ghc-devs
evs-boun...@haskell.org>> On Behalf Of Erdi, Gergo via ghc-devs Sent: 01 December 2021 05:22 To: 'GHC' mailto:ghc-devs@haskell.org>> Subject: [EXTERNAL] Recognizing default method implementations PUBLIC Hi, Is there a way to recognize that an Id / Var refers to a default m

Source locations from Core

2021-12-28 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I'm looking for ways to map Core fragments back to source locations. I see there is an annotated version of Core in `GHC/Core.hs` called `AnnExpr`, which I could see being useful for this if I set the annotation type to `SrcSpan`, but that's not what I get out of GHC's desugarer, si

RE: [External] Re: Source locations from Core

2021-12-28 Thread Erdi, Gergo via ghc-devs
PUBLIC Thank you, this looks exactly like what I'm looking for. Now I'll just have to try it on larger examples to see how approximate it is 😊 -Original Message- From: Matthew Pickering Sent: Tuesday, December 28, 2021 10:36 AM To: Erdi, Gergo Cc: GHC Subject: [External] Re: Source l

What's the benefit of taking "do" blocks apart? Is there a way to turn that off?

2021-12-28 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I'm seeing 'do' blocks getting taking apart into top-level definitions, so e.g. main = do some complicated expression 1 some complicated expression 2 is compiled into sat_sKv = some complicated expression 1 sat_sKw = \_ -> some complicated expression 2 main = bindIO sat_sKv sat_

Avoiding full laziness xform / floating-out (Re: What's the benefit of taking "do" blocks apart? Is there a way to turn that off?)

2021-12-30 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi Joachim, Thanks for the hints! > Hi Gergo, > > Am Dienstag, dem 28.12.2021 um 15:57 + schrieb Erdi, Gergo via ghc- > devs: > > PUBLIC > > phew Yeah obviously I'm sitting here not only adding these tags, but also coming up with the automated systems

RE: [External] Re: Avoiding full laziness xform / floating-out (Re: What's the benefit of taking "do" blocks apart? Is there a way to turn that off?)

2021-12-30 Thread Erdi, Gergo via ghc-devs
apart? Is there a way to turn that off?) Hi Gergo, Sounds like you might be better off writing your own optimisation pass rather than relying on making GHC do what you want. Cheers Matt On Thu, Dec 30, 2021 at 9:05 AM Erdi, Gergo via ghc-devs wrote: > > PUBLIC > > Hi Joachim, >

Re: Avoiding full laziness xform / floating-out (Re: What's the benefit of taking "do" blocks apart? Is there a way to turn that off?)

2021-12-30 Thread Erdi, Gergo via ghc-devs
Is there a way to turn that off?) Hi Gergo, Sounds like you might be better off writing your own optimisation pass rather than relying on making GHC do what you want. Cheers Matt On Thu, Dec 30, 2021 at 9:05 AM Erdi, Gergo via ghc-devs wrote: > > PUBLIC > > Hi Joachim, > >

Where do I put the *definition* of a DFunId?

2022-02-10 Thread Erdi, Gergo via ghc-devs
PUBLIC PUBLIC Hi, I'm trying to make a module out of thin air and register it to GHC so that other modules can import it. So far, I have had success with making a ModIface and a ModDetails, and then registering them using the following function: registerModule :: (GhcMonad m) => ModIface ->

RE: Where do I put the *definition* of a DFunId?

2022-02-15 Thread Erdi, Gergo via ghc-devs
PUBLIC > I'm not surprised that eventually it crashes and burns, because, > again, I have only declared my DFunId ('$fShowOrderPolicy' in this > case), but never defined it. Its definition would be a CoreExpr, > right? So where would I put the pair of '(dfun, > myCoreExprOfTheRightType)' for GHC t

RE: Re: Shadowing in toIface* output

2022-04-04 Thread Erdi, Gergo via ghc-devs
PUBLIC OK, I must be doing something wrong then. I am now looking at Tidy (not Prep) output, and I see Core like this: showsPrec :: forall a. Show a => Int -> a -> ShowS [GblId[ClassOp], Arity=1, Caf=NoCafRefs, Str=, RULES: Built in rule for showsPrec: "Class op showsPrec"] sho

RE: Re: Shadowing in toIface* output

2022-04-04 Thread Erdi, Gergo via ghc-devs
odule and 2. How do I fill in these missing pieces during reconstruction? From: ghc-devs On Behalf Of Erdi, Gergo via ghc-devs Sent: Tuesday, April 5, 2022 11:09 AM To: Simon Peyton Jones ; Gergo Érdi Cc: GHC Devs Subject: [External] RE: Re: Shadowing in toIface* output OK, I must be

Re: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings

2022-04-05 Thread Erdi, Gergo via ghc-devs
PUBLIC Just so this isn't prematurely all lost, I went back and looked for this example. With the following two definitions: subsequences:: [a] -> [[a]] subsequences xs = [] : nonEmptySubsequences xs nonEmptySubsequences :: [a] -> [[a]] nonEmptySubsequences []

Re: Avoiding `OtherCon []` unfoldings, restoring definitions from unfoldings

2022-04-06 Thread Erdi, Gergo via ghc-devs
PUBLIC Please see this question in my previous email: * Unfortunately, I am unable to reproduce this from the command line using the GHC executable, so before I put in the effort of making a minimal example of using the GHC API to get this result, I would first like to know if this is eve

RE: [External] Re: Specialising NOINLINE functions

2022-05-08 Thread Erdi, Gergo via ghc-devs
PUBLIC I can look into this, sure, but it wouldn't exactly solve my original problem, which is that I would like to turn this on wholesale, not definition by definition. It seems that all past discussion about this was in the context of a per-definition pragma (and sadly, a large part of that w

Migration guide for multiple home units

2022-06-15 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, Is there a migration guide for GHC API clients for the new "multiple home units" feature? In particular, I have the following two functions in my code that used to interact with related features of GHC: addUnit :: UnitInfo -> HscEnv -> HscEnv addUnit unitInfo@GenericUnitInfo{..}

Re: Migration guide for multiple home units

2022-06-19 Thread Erdi, Gergo via ghc-devs
: Erdi, Gergo Cc: GHC Devs ; Montelatici, Raphael Laurent Subject: [External] Re: Migration guide for multiple home units On Thu, 16 Jun 2022, Erdi, Gergo via ghc-devs wrote: > Is there a migration guide for GHC API clients for the new “multiple home > units” > feature? OK so i

Re: Migration guide for multiple home units

2022-06-21 Thread Erdi, Gergo via ghc-devs
ding as its own home unit, because > > that then leads to module name resolution problems in `main`: every > > imported module from `main` is searched for in `main` instead of its > > correct unit. > > > > 2. Speaking of `main`, why is it that when adding units, I have to

RE: Migration guide for multiple home units

2022-06-30 Thread Erdi, Gergo via ghc-devs
PUBLIC In case anyone finds this interesting, I ended up splitting the unit initialization into two parts: one where all units are registered, without any package dependencies, and one where the package dependencies of a single unit are registered. This allowed us to start with just knowing whi

Re: Partial type synonyms -- first-class!

2022-08-12 Thread Erdi, Gergo via ghc-devs
PUBLIC For anyone interested, I've added MRs https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8818 and https://gitlab.haskell.org/ghc/ghc/-/merge_requests/8819 to track my progress. From: ghc-devs On Behalf Of Edward Kmett Sent: Friday, August 12, 2022 10:43 AM To: ÉRDI Gergő Cc: GHC Devs

Test failures on `master`

2022-08-15 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, As of dca43a04fb, I am seeing the following test failures locally. Is this due to some configuration problem in my development environment, or did something slip through CI? Thanks, Gergo Unexpected failures: /tmp/ghctest-2v5a6979/test spaces/testsuite/tests/drive

Looking up names in an "opportunistic" type checker plugin

2022-10-03 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I'm writing a type checker plugin that should do things whenever used in the context of a module that already has some definitions loaded. I've hacked together the following function using internal details that I feel I should not be using: lookupOrigMaybe :: Module -> OccName -> T

Missing class op rules when using API

2022-10-17 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, I'm trying to compile the following two modules: ``` {-# LANGUAGE NoImplicitPrelude #-} module MiniMonad where class Functor f where fmap :: (a -> b) -> f a -> f b class (Functor f) => Applicative f where pure :: a -> f a class (Applicative m) => Monad m where return ::

RE: Missing class op rules when using API

2022-10-17 Thread Erdi, Gergo via ghc-devs
where, that the ModDetails from tidyProgram is not good for all purposes? Should its type be different, then, from an all-purpose ModDetails? From: ghc-devs On Behalf Of Erdi, Gergo via ghc-devs Sent: Monday, October 17, 2022 6:33 PM To: ghc-devs@haskell.org Subject: [External] Missing class op

RE: [External] Is Prep supposed to keep thing in (reverse) dependency order?

2022-11-03 Thread Erdi, Gergo via ghc-devs
PUBLIC Never mind, I think I got myself confused about different stages of the pipeline. The order of binds generated by Prep is correct, what was tripping me up really was that sat_s2iCp is a local Id bound by a top-level bind. But that's OK, I handle this situation now and everything else wor

Almost all tests fail after 08bf28819b

2022-11-22 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, Even though I've rebuilt everything from scratch, I'm unable to run most tests on `master` from (including) 08bf28819b78e740550a73a90eda62cce8d21c90. The error message is the same for all tests: ghc: /home/mi/prog/ghc/_build/stage1/lib/x86_64-linux-ghc-9.5.20221122/base-4.17.0.0/HS

Re: Almost all tests fail after 08bf28819b

2022-11-23 Thread Erdi, Gergo via ghc-devs
PUBLIC Nope, still getting the same error after deleting all of _build. I'm also on AMD64 Linux. I've tried with GHC 9.2.5 and 9.4.3. For reference, my exact command line (after deleting _build) is: ./boot && ./configure && ./hadrian/build-stack --flavour=devel2 -j10 test --only="ann01"

Re: Almost all tests fail after 08bf28819b

2022-11-24 Thread Erdi, Gergo via ghc-devs
PUBLIC Thanks, I can confirm I was able to build and validate on the devel2 flavour with this commit merged. From: Cheng Shao Sent: Friday, November 25, 2022 6:27 AM To: Matthew Farkas-Dyck Cc: Erdi, Gergo ; ghc-devs@haskell.org Subject: [External] Re: Almost all tests fail after 08bf28819b T

RE: 9.4.4 release

2022-12-14 Thread Erdi, Gergo via ghc-devs
PUBLIC I'd like to nominate !9153 since it fixes a regression from 9.2 to 9.4. Also, I don't know why but I was unable to make this comment on the MR, because I keep getting: "Your comment could not be submitted! Please check your network connection and try again." Even though I can otherwise

RE: [External] Re: Usage of Template Haskell quotes in GHC source tree vs. usage of GHC as a library

2023-07-12 Thread Erdi, Gergo via ghc-devs
PUBLIC https://gitlab.haskell.org/ghc/ghc/-/issues/23647 From: ghc-devs On Behalf Of Simon Peyton Jones Sent: Wednesday, July 12, 2023 7:25 PM To: Gergő Érdi Cc: GHC Devs Subject: [External] Re: Usage of Template Haskell quotes in GHC source tree vs. usage of GHC as a library ATTENTION: This

Weird pipeline failures

2023-08-21 Thread Erdi, Gergo via ghc-devs
PUBLIC Hi, On e.g. https://gitlab.haskell.org/ghc/ghc/-/commit/9b4fe2a39952b0a463bcf67f1b357b8364f6725e/pipelines I am seeing very weird failures tagged "yaml invalid": Unable to create pipeline * 'test-primops-validate' job needs 'x86_64-linux-deb10-validate+debug_info' job, but 'x86_6