[Git][ghc/ghc][wip/marge_bot_batch_merge_job] 5 commits: Use TemplateHaskellQuotes in TH.Syntax to construct Names

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri May 5 17:42:31 UTC 2023



Marge Bot pushed to branch wip/marge_bot_batch_merge_job at Glasgow Haskell Compiler / GHC


Commits:
983ce558 by Oleg Grenrus at 2023-05-05T13:11:29-04:00
Use TemplateHaskellQuotes in TH.Syntax to construct Names

- - - - -
9abd0bd8 by Matthew Pickering at 2023-05-05T13:42:22-04:00
driver: Use hooks from plugin_hsc_env

This fixes a bug in oneshot mode where hooks modified in a plugin
wouldn't be used in oneshot mode because we neglected to use the right
hsc_env. This was observed by @csabahruska.

- - - - -
01f0f5a6 by Aaron Allen at 2023-05-05T13:42:22-04:00
Rework plugin initialisation points

In general this patch pushes plugin initialisation points to earlier in
the pipeline. As plugins can modify the `HscEnv`, it's imperative that
the plugins are initialised as soon as possible and used thereafter.

For example, there are some new tests which modify hsc_logger and other
hooks which failed to fire before (and now do)

One consequence of this change is that the error for specifying the
usage of a HPT plugin from the command line has changed, because it's
now attempted to be loaded at initialisation rather than causing a
cyclic module import.

Closes #21279

Co-authored-by: Matthew Pickering <matthewtpickering at gmail.com>

- - - - -
07ccfc64 by Matthew Pickering at 2023-05-05T13:42:22-04:00
docs: Add Note [Timing of plugin initialization]

- - - - -
ad010960 by Matthew Pickering at 2023-05-05T13:42:22-04:00
Incrementally update ghcup metadata in ghc/ghcup-metadata

This job paves the way for distributing nightly builds

* A new repo https://gitlab.haskell.org/ghc/ghcup-metadata stores the
  metadata on the "updates" branch.
* Each night this metadata is downloaded and the nightly builds are
  appended to the end of the metadata.
* The update job only runs on the scheduled nightly pipeline, not just
  when NIGHTLY=1.

Things which are not done yet

* Modify the retention policy for nightly jobs
* Think about building release flavour compilers to distribute nightly.

Fixes #23334

- - - - -


18 changed files:

- .gitlab-ci.yml
- compiler/GHC/Driver/Make.hs
- compiler/GHC/Driver/Pipeline.hs
- compiler/GHC/Driver/Pipeline/Execute.hs
- compiler/GHC/Runtime/Loader.hs
- ghc/Main.hs
- libraries/template-haskell/Language/Haskell/TH/Syntax.hs
- testsuite/tests/plugins/all.T
- + testsuite/tests/plugins/hooks-plugin/Hooks/LogPlugin.hs
- testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs → testsuite/tests/plugins/hooks-plugin/Hooks/MetaPlugin.hs
- + testsuite/tests/plugins/hooks-plugin/Hooks/PhasePlugin.hs
- testsuite/tests/plugins/hooks-plugin/hooks-plugin.cabal
- testsuite/tests/plugins/plugins04.stderr
- testsuite/tests/plugins/test-hooks-plugin.hs
- + testsuite/tests/plugins/test-log-hooks-plugin.hs
- + testsuite/tests/plugins/test-log-hooks-plugin.stderr
- + testsuite/tests/plugins/test-phase-hooks-plugin.hs
- + testsuite/tests/plugins/test-phase-hooks-plugin.stderr


Changes:

=====================================
.gitlab-ci.yml
=====================================
@@ -999,7 +999,7 @@ project-version:
     - . ./version.sh
 
     # Download existing ghcup metadata
-    - nix shell --extra-experimental-features nix-command --extra-experimental-features flakes nixpkgs#wget -c wget "https://raw.githubusercontent.com/haskell/ghcup-metadata/develop/ghcup-0.0.7.yaml"
+    - nix shell --extra-experimental-features nix-command --extra-experimental-features flakes nixpkgs#wget -c wget "https://gitlab.haskell.org/ghc/ghcup-metadata/-/raw/updates/ghcup-0.0.7.yaml"
 
     - .gitlab/generate_job_metadata
 
@@ -1048,6 +1048,37 @@ ghcup-metadata-nightly:
   rules:
     - if: $NIGHTLY
 
+# Update the
+ghcup-metadata-nightly-push:
+  stage: deploy
+  image: "registry.gitlab.haskell.org/ghc/ci-images/x86_64-linux-fedora33:$DOCKER_REV"
+  dependencies: null
+  tags:
+    - x86_64-linux
+  variables:
+    BUILD_FLAVOUR: default
+    GIT_SUBMODULE_STRATEGY: "none"
+  needs:
+    - job: ghcup-metadata-nightly
+      artifacts: true
+  script:
+    - git clone https://gitlab.haskell.org/ghc/ghcup-metadata.git
+    - cp metadata_test.yaml ghcup-metadata/ghcup-0.0.7.yaml
+    - cd ghcup-metadata
+    - git config user.email "ghc-ci at gitlab-haskell.org"
+    - git config user.name "GHC GitLab CI"
+    - git remote add gitlab_origin https://oauth2:$PROJECT_PUSH_TOKEN@gitlab.haskell.org/ghc/ghcup-metadata.git
+    - git add .
+    - git commit -m "Update metadata"
+    - git push gitlab_origin HEAD:updates -o ci.skip
+  rules:
+    - if: $NIGHTLY
+    # Only run the update on scheduled nightly pipelines, ie once a day
+    - if: $CI_PIPELINE_SOURCE == "schedule"
+    # And only update the metadata for master branch
+    - if: '$CI_COMMIT_BRANCH == "master"'
+
+
 ghcup-metadata-release:
   # No explicit needs for release pipeline as we assume we need everything and everything will pass.
   extends: .ghcup-metadata


=====================================
compiler/GHC/Driver/Make.hs
=====================================
@@ -694,6 +694,10 @@ data WorkerLimit
 -- produced by calling 'depanal'.
 load' :: GhcMonad m => Maybe ModIfaceCache -> LoadHowMuch -> Maybe Messager -> ModuleGraph -> m SuccessFlag
 load' mhmi_cache how_much mHscMessage mod_graph = do
+    -- In normal usage plugins are initialised already by ghc/Main.hs this is protective
+    -- for any client who might interact with GHC via load'.
+    -- See Note [Timing of plugin initialization]
+    initializeSessionPlugins
     modifySession $ \hsc_env -> hsc_env { hsc_mod_graph = mod_graph }
     guessOutputFile
     hsc_env <- getSession
@@ -2852,13 +2856,11 @@ label_self thread_name = do
 runPipelines :: WorkerLimit -> HscEnv -> Maybe Messager -> [MakeAction] -> IO ()
 -- Don't even initialise plugins if there are no pipelines
 runPipelines _ _ _ [] = return ()
-runPipelines n_job orig_hsc_env mHscMessager all_pipelines = do
+runPipelines n_job hsc_env mHscMessager all_pipelines = do
   liftIO $ label_self "main --make thread"
-
-  plugins_hsc_env <- initializePlugins orig_hsc_env
   case n_job of
-    NumProcessorsLimit n | n <= 1 -> runSeqPipelines plugins_hsc_env mHscMessager all_pipelines
-    _n -> runParPipelines n_job plugins_hsc_env mHscMessager all_pipelines
+    NumProcessorsLimit n | n <= 1 -> runSeqPipelines hsc_env mHscMessager all_pipelines
+    _n -> runParPipelines n_job hsc_env mHscMessager all_pipelines
 
 runSeqPipelines :: HscEnv -> Maybe Messager -> [MakeAction] -> IO ()
 runSeqPipelines plugin_hsc_env mHscMessager all_pipelines =


=====================================
compiler/GHC/Driver/Pipeline.hs
=====================================
@@ -244,12 +244,13 @@ compileOne' mHscMessage
              addFilesToClean tmpfs TFL_GhcSession $
                  [ml_obj_file $ ms_location summary]
 
+   -- Initialise plugins here for any plugins enabled locally for a module.
    plugin_hsc_env <- initializePlugins hsc_env
    let pipe_env = mkPipeEnv NoStop input_fn Nothing pipelineOutput
    status <- hscRecompStatus mHscMessage plugin_hsc_env upd_summary
                 mb_old_iface mb_old_linkable (mod_index, nmods)
    let pipeline = hscPipeline pipe_env (setDumpPrefix pipe_env plugin_hsc_env, upd_summary, status)
-   (iface, linkable) <- runPipeline (hsc_hooks hsc_env) pipeline
+   (iface, linkable) <- runPipeline (hsc_hooks plugin_hsc_env) pipeline
    -- See Note [ModDetails and --make mode]
    details <- initModDetails plugin_hsc_env iface
    linkable' <- traverse (initWholeCoreBindings plugin_hsc_env iface details) (homeMod_bytecode linkable)
@@ -526,7 +527,12 @@ findHSLib platform ws dirs lib = do
 -- Compile files in one-shot mode.
 
 oneShot :: HscEnv -> StopPhase -> [(String, Maybe Phase)] -> IO ()
-oneShot hsc_env stop_phase srcs = do
+oneShot orig_hsc_env stop_phase srcs = do
+  -- In oneshot mode, initialise plugins specified on command line
+  -- we also initialise in ghc/Main but this might be used as an entry point by API clients who
+  -- should initialise their own plugins but may not.
+  -- See Note [Timing of plugin initialization]
+  hsc_env <- initializePlugins orig_hsc_env
   o_files <- mapMaybeM (compileFile hsc_env stop_phase) srcs
   case stop_phase of
     StopPreprocess -> return ()


=====================================
compiler/GHC/Driver/Pipeline/Execute.hs
=====================================
@@ -62,7 +62,6 @@ import GHC.Parser.Header
 import GHC.Data.StringBuffer
 import GHC.Types.SourceError
 import GHC.Unit.Finder
-import GHC.Runtime.Loader
 import Data.IORef
 import GHC.Types.Name.Env
 import GHC.Platform.Ways
@@ -82,6 +81,7 @@ import GHC.StgToJS.Linker.Linker (embedJsFile)
 
 import Language.Haskell.Syntax.Module.Name
 import GHC.Unit.Home.ModInfo
+import GHC.Runtime.Loader (initializePlugins)
 
 newtype HookedUse a = HookedUse { runHookedUse :: (Hooks, PhaseHook) -> IO a }
   deriving (Functor, Applicative, Monad, MonadIO, MonadThrow, MonadCatch) via (ReaderT (Hooks, PhaseHook) IO)
@@ -724,9 +724,11 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
       new_includes = addImplicitQuoteInclude paths [current_dir]
       paths = includePaths dflags0
       dflags = dflags0 { includePaths = new_includes }
-      hsc_env = hscSetFlags dflags hsc_env0
-
+      hsc_env1 = hscSetFlags dflags hsc_env0
 
+  -- Initialise plugins as the flags passed into runHscPhase might have local plugins just
+  -- specific to this module.
+  hsc_env <- initializePlugins hsc_env1
 
   -- gather the imports and module name
   (hspp_buf,mod_name,imps,src_imps, ghc_prim_imp) <- do
@@ -786,18 +788,17 @@ runHscPhase pipe_env hsc_env0 input_fn src_flavour = do
   -- run the compiler!
   let msg :: Messager
       msg hsc_env _ what _ = oneShotMsg (hsc_logger hsc_env) what
-  plugin_hsc_env' <- initializePlugins hsc_env
 
   -- Need to set the knot-tying mutable variable for interface
   -- files. See GHC.Tc.Utils.TcGblEnv.tcg_type_env_var.
   -- See also Note [hsc_type_env_var hack]
   type_env_var <- newIORef emptyNameEnv
-  let plugin_hsc_env = plugin_hsc_env' { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)]) }
+  let hsc_env' = hsc_env { hsc_type_env_vars = knotVarsFromModuleEnv (mkModuleEnv [(mod, type_env_var)]) }
 
-  status <- hscRecompStatus (Just msg) plugin_hsc_env mod_summary
+  status <- hscRecompStatus (Just msg) hsc_env' mod_summary
                         Nothing emptyHomeModInfoLinkable (1, 1)
 
-  return (plugin_hsc_env, mod_summary, status)
+  return (hsc_env', mod_summary, status)
 
 -- | Calculate the ModLocation from the provided DynFlags. This function is only used
 -- in one-shot mode and therefore takes into account the effect of -o/-ohi flags


=====================================
compiler/GHC/Runtime/Loader.hs
=====================================
@@ -2,7 +2,7 @@
 
 -- | Dynamically lookup up values from modules and loading them.
 module GHC.Runtime.Loader (
-        initializePlugins,
+        initializePlugins, initializeSessionPlugins,
         -- * Loading plugins
         loadFrontendPlugin,
 
@@ -74,7 +74,34 @@ import Unsafe.Coerce     ( unsafeCoerce )
 import GHC.Linker.Types
 import Data.List (unzip4)
 import GHC.Iface.Errors.Ppr
+import GHC.Driver.Monad
 
+{- Note [Timing of plugin initialization]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+
+Plugins needs to be initialised as soon as possible in the pipeline. This is because
+driver plugins are executed immediately after being loaded, which can modify anything
+in the HscEnv, including the logger and DynFlags (for example #21279). For example,
+in ghc/Main.hs the logger is used almost immediately after the session has been initialised
+and so if a user overwrites the logger expecting all output to go there then unless
+the plugins are initialised before that point then unexpected things will happen.
+
+We initialise plugins in ghc/Main.hs for the main ghc executable.
+
+When people are using the GHC API, they also need to initialise plugins
+at the highest level possible for things to work as expected. We keep
+some defensive calls to plugin initialisation in functions like `load'` and `oneshot`
+to catch cases where API users have not initialised their own plugins.
+
+In addition to this, there needs to be an initialisation call for each module
+just in case the user has enabled a plugin just for that module using OPTIONS_GHC
+pragma.
+
+-}
+
+-- | Initialise plugins specified by the current DynFlags and update the session.
+initializeSessionPlugins :: GhcMonad m => m ()
+initializeSessionPlugins = getSession >>= liftIO . initializePlugins >>= setSession
 
 -- | Loads the plugins specified in the pluginModNames field of the dynamic
 -- flags. Should be called after command line arguments are parsed, but before


=====================================
ghc/Main.hs
=====================================
@@ -41,7 +41,7 @@ import GHC.Platform.Host
 import GHCi.UI              ( interactiveUI, ghciWelcomeMsg, defaultGhciSettings )
 #endif
 
-import GHC.Runtime.Loader   ( loadFrontendPlugin )
+import GHC.Runtime.Loader   ( loadFrontendPlugin, initializeSessionPlugins )
 
 import GHC.Unit.Env
 import GHC.Unit (UnitId, homeUnitDepends)
@@ -257,16 +257,23 @@ main' postLoadMode units dflags0 args flagWarnings = do
   -- we've finished manipulating the DynFlags, update the session
   _ <- GHC.setSessionDynFlags dflags5
   dflags6 <- GHC.getSessionDynFlags
-  hsc_env <- GHC.getSession
+
+  -- Must do this before loading plugins
+  liftIO $ initUniqSupply (initialUnique dflags6) (uniqueIncrement dflags6)
+
+  -- Initialise plugins here because the plugin author might already expect this
+  -- subsequent call to `getLogger` to be affected by a plugin.
+  initializeSessionPlugins
+  hsc_env <- getSession
   logger <- getLogger
 
+
         ---------------- Display configuration -----------
   case verbosity dflags6 of
     v | v == 4 -> liftIO $ dumpUnitsSimple hsc_env
       | v >= 5 -> liftIO $ dumpUnits       hsc_env
       | otherwise -> return ()
 
-  liftIO $ initUniqSupply (initialUnique dflags6) (uniqueIncrement dflags6)
         ---------------- Final sanity checking -----------
   liftIO $ checkOptions postLoadMode dflags6 srcs objs units
 


=====================================
libraries/template-haskell/Language/Haskell/TH/Syntax.hs
=====================================
@@ -6,6 +6,7 @@
              Trustworthy, DeriveFunctor, BangPatterns, RecordWildCards, ImplicitParams #-}
 
 {-# OPTIONS_GHC -fno-warn-inline-rule-shadowing #-}
+{-# LANGUAGE TemplateHaskellQuotes #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -54,7 +55,7 @@ import Data.Ratio
 import GHC.CString      ( unpackCString# )
 import GHC.Generics     ( Generic )
 import GHC.Types        ( Int(..), Word(..), Char(..), Double(..), Float(..),
-                          TYPE, RuntimeRep(..) )
+                          TYPE, RuntimeRep(..), Multiplicity (..) )
 import GHC.Prim         ( Int#, Word#, Char#, Double#, Float#, Addr# )
 import GHC.Ptr          ( Ptr, plusPtr )
 import GHC.Lexeme       ( startsVarSym, startsVarId )
@@ -65,7 +66,6 @@ import Prelude hiding (Applicative(..))
 import Foreign.ForeignPtr
 import Foreign.C.String
 import Foreign.C.Types
-import GHC.Stack
 
 #if __GLASGOW_HASKELL__ >= 901
 import GHC.Types ( Levity(..) )
@@ -1067,8 +1067,7 @@ instance Lift (Fixed.Fixed a) where
     ex <- lift x
     return (ConE mkFixedName `AppE` ex)
     where
-      mkFixedName =
-        mkNameG DataName "base" "Data.Fixed" "MkFixed"
+      mkFixedName = 'Fixed.MkFixed
 
 instance Integral a => Lift (Ratio a) where
   liftTyped x = unsafeCodeCoerce (lift x)
@@ -1139,19 +1138,8 @@ instance Lift ByteArray where
       ptr :: ForeignPtr Word8
       ptr = ForeignPtr (byteArrayContents# pb) (PlainPtr (unsafeCoerce# pb))
 
-
--- We can't use a TH quote in this module because we're in the template-haskell
--- package, so we conconct this quite defensive solution to make the correct name
--- which will work if the package name or module name changes in future.
 addrToByteArrayName :: Name
-addrToByteArrayName = helper
-  where
-    helper :: HasCallStack => Name
-    helper =
-      case getCallStack ?callStack of
-        [] -> error "addrToByteArrayName: empty call stack"
-        (_, SrcLoc{..}) : _ -> mkNameG_v srcLocPackage srcLocModule "addrToByteArray"
-
+addrToByteArrayName = 'addrToByteArray
 
 addrToByteArray :: Int -> Addr# -> ByteArray
 addrToByteArray (I# len) addr = runST $ ST $
@@ -1371,23 +1359,24 @@ instance (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g)
 
 
 trueName, falseName :: Name
-trueName  = mkNameG DataName "ghc-prim" "GHC.Types" "True"
-falseName = mkNameG DataName "ghc-prim" "GHC.Types" "False"
+trueName  = 'True
+falseName = 'False
 
 nothingName, justName :: Name
-nothingName = mkNameG DataName "base" "GHC.Maybe" "Nothing"
-justName    = mkNameG DataName "base" "GHC.Maybe" "Just"
+nothingName = 'Nothing
+justName    = 'Just
 
 leftName, rightName :: Name
-leftName  = mkNameG DataName "base" "Data.Either" "Left"
-rightName = mkNameG DataName "base" "Data.Either" "Right"
+leftName  = 'Left
+rightName = 'Right
 
 nonemptyName :: Name
-nonemptyName = mkNameG DataName "base" "GHC.Base" ":|"
+nonemptyName = '(:|)
 
 oneName, manyName :: Name
-oneName  = mkNameG DataName "ghc-prim" "GHC.Types" "One"
-manyName = mkNameG DataName "ghc-prim" "GHC.Types" "Many"
+oneName  = 'One
+manyName = 'Many
+
 -----------------------------------------------------
 --
 --              Generic Lift implementations


=====================================
testsuite/tests/plugins/all.T
=====================================
@@ -317,3 +317,17 @@ test('plugins-external',
       pre_cmd('$MAKE -s --no-print-directory -C shared-plugin package.plugins01 TOP={top}'),
       when(opsys('linux') and not ghc_dynamic(), expect_broken(20706))],
      makefile_test, [])
+
+test('test-phase-hooks-plugin',
+     [extra_files(['hooks-plugin/']),
+      pre_cmd('$MAKE -s --no-print-directory -C hooks-plugin package.test-phase-hooks-plugin TOP={top}'),
+
+      when(opsys('linux') and not ghc_dynamic(), expect_broken(20706))],
+     compile,
+     ['-package-db hooks-plugin/pkg.test-phase-hooks-plugin/local.package.conf -fplugin Hooks.PhasePlugin -package hooks-plugin ' + config.plugin_way_flags])
+
+test('test-log-hooks-plugin',
+     [extra_files(['hooks-plugin/']),
+      pre_cmd('$MAKE -s --no-print-directory -C hooks-plugin package.test-log-hooks-plugin TOP={top}')],
+     compile_fail,
+     ['-package-db hooks-plugin/pkg.test-log-hooks-plugin/local.package.conf -fplugin Hooks.LogPlugin -package hooks-plugin ' + config.plugin_way_flags])


=====================================
testsuite/tests/plugins/hooks-plugin/Hooks/LogPlugin.hs
=====================================
@@ -0,0 +1,24 @@
+module Hooks.LogPlugin (plugin) where
+
+import GHC.Plugins
+import GHC.Driver.Hooks
+import GHC.Tc.Utils.Monad
+import GHC.Utils.Logger
+import GHC.Driver.Pipeline.Execute
+import System.IO
+
+plugin :: Plugin
+plugin = defaultPlugin { driverPlugin = hooksP }
+
+hooksP :: [CommandLineOption] -> HscEnv -> IO HscEnv
+hooksP opts hsc_env = do
+  hSetBuffering stdout NoBuffering
+  let logger  = hsc_logger hsc_env
+      logger' = pushLogHook logHook logger
+      hsc_env' = hsc_env { hsc_logger = logger' }
+  return hsc_env'
+
+logHook :: LogAction -> LogAction
+logHook action logFlags messageClass srcSpan msgDoc = do
+  putStrLn "Log hook called"
+  action logFlags messageClass srcSpan msgDoc


=====================================
testsuite/tests/plugins/hooks-plugin/Hooks/Plugin.hs → testsuite/tests/plugins/hooks-plugin/Hooks/MetaPlugin.hs
=====================================
@@ -1,5 +1,5 @@
 {-# OPTIONS_GHC -Wall #-}
-module Hooks.Plugin (plugin) where
+module Hooks.MetaPlugin (plugin) where
 
 import GHC.Types.SourceText
 import GHC.Plugins


=====================================
testsuite/tests/plugins/hooks-plugin/Hooks/PhasePlugin.hs
=====================================
@@ -0,0 +1,30 @@
+{-# LANGUAGE GADTs #-}
+{-# OPTIONS_GHC -Wall #-}
+module Hooks.PhasePlugin (plugin) where
+
+import GHC.Plugins
+import GHC.Driver.Hooks
+import GHC.Tc.Utils.Monad
+import GHC.Driver.Pipeline.Execute
+import GHC.Driver.Pipeline.Phases
+import System.IO
+
+plugin :: Plugin
+plugin = defaultPlugin { driverPlugin = hooksP }
+
+hooksP :: [CommandLineOption] -> HscEnv -> IO HscEnv
+hooksP opts hsc_env = do
+  hSetBuffering stdout NoBuffering
+  let hooks  = hsc_hooks hsc_env
+      hooks' = hooks { runPhaseHook = Just fakeRunPhaseHook }
+      hsc_env' = hsc_env { hsc_hooks = hooks' }
+  return hsc_env'
+
+fakeRunPhaseHook :: PhaseHook
+fakeRunPhaseHook = PhaseHook $ \tPhase -> do
+  liftIO $ case tPhase of
+    T_Cpp{} -> putStrLn "Cpp hook fired"
+    T_Hsc{} -> putStrLn "Hsc hook fired"
+    T_FileArgs{} -> putStrLn "FileArgs hook fired"
+    _ -> pure ()
+  runPhase tPhase


=====================================
testsuite/tests/plugins/hooks-plugin/hooks-plugin.cabal
=====================================
@@ -4,6 +4,6 @@ version:             0.1
 build-type:          Simple
 
 library
-  exposed-modules:     Hooks.Plugin
+  exposed-modules:     Hooks.MetaPlugin, Hooks.PhasePlugin, Hooks.LogPlugin
   build-depends:       base, ghc
   default-language:    Haskell2010


=====================================
testsuite/tests/plugins/plugins04.stderr
=====================================
@@ -1,2 +1 @@
-Module graph contains a cycle:
-  module ‘HomePackagePlugin’ (./HomePackagePlugin.hs) imports itself
+attempting to use module ‘main:HomePackagePlugin’ (./HomePackagePlugin.hs) which is not loaded


=====================================
testsuite/tests/plugins/test-hooks-plugin.hs
=====================================
@@ -1,4 +1,4 @@
-{-# OPTIONS -fplugin=Hooks.Plugin #-}
+{-# OPTIONS -fplugin=Hooks.MetaPlugin #-}
 {-# LANGUAGE TemplateHaskell #-}
 module Main where
 


=====================================
testsuite/tests/plugins/test-log-hooks-plugin.hs
=====================================
@@ -0,0 +1,4 @@
+module Main where
+
+main :: IO ()
+main = pure "type error"


=====================================
testsuite/tests/plugins/test-log-hooks-plugin.stderr
=====================================
@@ -0,0 +1,9 @@
+Log hook called
+
+test-log-hooks-plugin.hs:4:13: error: [GHC-83865]
+    • Couldn't match type ‘[Char]’ with ‘()’
+      Expected: ()
+        Actual: String
+    • In the first argument of ‘pure’, namely ‘"type error"’
+      In the expression: pure "type error"
+      In an equation for ‘main’: main = pure "type error"


=====================================
testsuite/tests/plugins/test-phase-hooks-plugin.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE CPP #-}
+module Main where
+
+main :: IO ()
+main = pure ()


=====================================
testsuite/tests/plugins/test-phase-hooks-plugin.stderr
=====================================
@@ -0,0 +1,5 @@
+FileArgs hook fired
+Cpp hook fired
+FileArgs hook fired
+FileArgs hook fired
+Hsc hook fired



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53c2d50d425d31e6aa1bc927df57e5f82e7d9d51...ad0109608cbabb6702e36fd85013ddc9d77020e8

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/compare/53c2d50d425d31e6aa1bc927df57e5f82e7d9d51...ad0109608cbabb6702e36fd85013ddc9d77020e8
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230505/a916e367/attachment-0001.html>


More information about the ghc-commits mailing list