Hi Gergo

The error tells you what you only have setup the HscEnv so that
there's one unit called main, but you are attempting to compile
something with unit id cortex-prim.

Perhaps you could be inspired by `setSessionDynFlags` which deals with
renaming the main unit id if you are compiling a unit which have a
different unit id. (See setUnitDynFlagsNoCheck).

Matt


On Thu, Jun 16, 2022 at 5:01 AM Erdi, Gergo via ghc-devs
<ghc-devs@haskell.org> wrote:
>
> 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{..} = modifyUnitState $ \us -> us
>
>     { packageNameMap = addToUFM (packageNameMap us) unitPackageName unitId
>
>     , unitInfoMap = M.insert unitId unitInfo $ unitInfoMap us
>
>     }
>
>
>
> registerModule :: (GhcMonad m) => ModDetails -> ModIface -> m ()
>
> registerModule details iface = modifySession $ extendHpt . addModule
>
>   where
>
>     hmi = HomeModInfo iface details Nothing
>
>
>
>     mod = mi_module iface
>
>     modOrig = ModOrigin (Just True) [] [] True
>
>
>
>     addModule = modifyUnitState $ \us -> us
>
>         { moduleNameProvidersMap = M.insert (moduleName mod) (M.singleton mod 
> modOrig) $ moduleNameProvidersMap us
>
>         }
>
>
>
>     extendHpt env = env
>
>         { hsc_unit_env = let ue = hsc_unit_env env in ue
>
>             { ue_hpt = addHomeModInfoToHpt hmi (hsc_HPT env)
>
>             }
>
>         }
>
>
>
> I implemented these using the following utility function:
>
>
>
> modifyUnitState :: (UnitState -> UnitState) -> HscEnv -> HscEnv
>
> modifyUnitState f env = env
>
>     { hsc_unit_env = let ue = hsc_unit_env env in ue
>
>         { ue_units = f (ue_units ue)
>
>         }
>
>     }
>
>
>
> With the recent changes to GHC, `modifyUnitState` doesn’t work anymore 
> because there is no single `UnitEnv` in the `HscEnv`. I tried updating the 
> `HomeUnitEnv` of the current unit:
>
>
>
> modifyUnitState :: (UnitState -> UnitState) -> HscEnv -> HscEnv
>
> modifyUnitState f env = env
>
>     { hsc_unit_env = let ue = hsc_unit_env env in
>
>             ue_updateHomeUnitEnv f' (ue_currentUnit ue) ue
>
>     }
>
>   where
>
>     f' hue = let units = homeUnitEnv_units hue in hue
>
>         { homeUnitEnv_units = f units
>
>         }
>
>
>
> but this leads to a panic:
>
>
>
>   GHC version 9.5.20220613:
>
>         Unit unknown to the internal unit environment
>
>
>
> unit (cortex-prim)
>
> pprInternalUnitMap
>
>   main (flags: main, Just main) ->
>
> Call stack:
>
>     CallStack (from HasCallStack):
>
>       callStackDoc, called at compiler/GHC/Utils/Panic.hs:182:37 in 
> ghc-lib-0.20220613-HQTH0nHhxeOCnJy5jYkZiX:GHC.Utils.Panic
>
>       pprPanic, called at compiler/GHC/Unit/Env.hs:450:14 in 
> ghc-lib-0.20220613-HQTH0nHhxeOCnJy5jYkZiX:GHC.Unit.Env
>
>       ue_findHomeUnitEnv, called at compiler/GHC/Unit/Env.hs:394:48 in 
> ghc-lib-0.20220613-HQTH0nHhxeOCnJy5jYkZiX:GHC.Unit.Env
>
>       ue_unitFlags, called at compiler/GHC/Driver/Env.hs:421:18 in 
> ghc-lib-0.20220613-HQTH0nHhxeOCnJy5jYkZiX:GHC.Driver.Env
>
>       hscSetActiveUnitId, called at compiler/GHC/Driver/Env.hs:416:34 in 
> ghc-lib-0.20220613-HQTH0nHhxeOCnJy5jYkZiX:GHC.Driver.Env
>
>       hscSetActiveHomeUnit, called at compiler/GHC/Driver/Make.hs:1853:15 in 
> ghc-lib-0.20220613-HQTH0nHhxeOCnJy5jYkZiX:GHC.Driver.Make
>
>
>
>
>
> What is the new way of registering a new unit or new module with GHC?
>
>
>
> 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