Hi Gergo,

Please see a minimal example in this gist.

https://gist.github.com/mpickering/5029c7f244c484c91d665bcbc6bc6406

Cheers,

Matt

On Fri, Jun 25, 2021 at 10:20 AM Erdi, Gergo via ghc-devs
<ghc-devs@haskell.org> wrote:
>
> PUBLIC
>
>
> Hi,
>
>
>
> I have the following to .hs files:
>
>
>
> MyLib.hs:
>
> module MyLib where
> …
>
> 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”, and then typecheck Test.hs, all in-proc 
> using the GHC API, without putting any other files on disk. How do I do that?
>
>
>
> What I tried is loading MyLib.hs after setting the homeUnitId in the DynFlags 
> to “my-unit”, then editing the packageNameMap in the unitState of the 
> DynFlags to may “my-pkg” to “my-unit”:
>
> setHomeUnit :: (GhcMonad m) => UnitId -> m ()
>
> setHomeUnit unitId = do
>
>     dflags <- getSessionDynFlags
>
>     modifySession $ \h -> h{ hsc_dflags = dflags{ homeUnitId = unitId } }
>
>
>
> registerUnit :: (GhcMonad m) => PackageName -> UnitId -> m ()
>
> registerUnit pkg unitId = modifySession $ \h -> h{ hsc_dflags = addUnit $ 
> hsc_dflags h }
>
>   where
>
>     addUnit dflags = dflags
>
>         { unitState = let us = unitState dflags in us
>
>             { packageNameMap = M.insert pkg (Indefinite unitId Nothing) $ 
> packageNameMap us
>
>             }
>
>         }
>
>
>
> pipeline = do
>
>         setHomeUnit myUnit
>
>         loadModule =<< typecheckModule =<< parseModule =<< modSumarryFor 
> “MyLib”
>
>         registerUnit myPkg myUnit
>
>
>
>         setHomeUnit mainUnitId
>
>         typecheckModule =<< parseModule =<< modSumarryFor “Test”
>
>
>
>
>
> Alas, this doesn’t work: the import of `MyLib` from `my-pkg` fails with:
>
>
>
> input/linking/Test.hs:5:1: error:
>
>     Could not find module ‘MyLib’
>
>     It is not a module in the current program, or in any known package.
>
>
>
> TBH I’m not very surprised that it didn’t work – that registerUnit function 
> is doing some pretty deep surgery on the unitState that probably breaks 
> several invariants. Still, I wasn’t able to find a better way – all the 
> functions in GHC.Unit.State seem to be for querying only.
>
>
>
> Thanks,
>
>             Gergo
>
>
> This email and any attachments are confidential and may also be privileged. 
> If you are not the intended recipient, please delete all copies and notify 
> the sender immediately. You may wish to refer to the incorporation details of 
> Standard Chartered PLC, Standard Chartered Bank and their subsidiaries at 
> https: //www.sc.com/en/our-locations
>
> Where you have a Financial Markets relationship with Standard Chartered PLC, 
> Standard Chartered Bank and their subsidiaries (the "Group"), information on 
> the regulatory standards we adhere to and how it may affect you can be found 
> in our Regulatory Compliance Statement at https: //www.sc.com/rcs/ and 
> Regulatory Compliance Disclosures at http: //www.sc.com/rcs/fm
>
> Insofar as this communication is not sent by the Global Research team and 
> contains any market commentary, the market commentary has been prepared by 
> the sales and/or trading desk of Standard Chartered Bank or its affiliate. It 
> is not and does not constitute research material, independent research, 
> recommendation or financial advice. Any market commentary is for information 
> purpose only and shall not be relied on for any other purpose and is subject 
> to the relevant disclaimers available at https: 
> //www.sc.com/en/regulatory-disclosures/#market-disclaimer.
>
> Insofar as this communication is sent by the Global Research team and 
> contains any research materials prepared by members of the team, the research 
> material is for information purpose only and shall not be relied on for any 
> other purpose, and is subject to the relevant disclaimers available at https: 
> //research.sc.com/research/api/application/static/terms-and-conditions.
>
> Insofar as this e-mail contains the term sheet for a proposed transaction, by 
> responding affirmatively to this e-mail, you agree that you have understood 
> the terms and conditions in the attached term sheet and evaluated the merits 
> and risks of the transaction. We may at times also request you to sign the 
> term sheet to acknowledge the same.
>
> Please visit https: //www.sc.com/en/regulatory-disclosures/dodd-frank/ for 
> important information with respect to derivative products.
> _______________________________________________
> 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

Reply via email to