[Git][ghc/ghc][wip/andreask/ppr_prelude] Remove Trace.hs-boot
Andreas Klebinger (@AndreasK)
gitlab at gitlab.haskell.org
Wed Nov 2 14:25:44 UTC 2022
Andreas Klebinger pushed to branch wip/andreask/ppr_prelude at Glasgow Haskell Compiler / GHC
Commits:
963f857c by Andreas Klebinger at 2022-11-02T15:23:00+01:00
Remove Trace.hs-boot
- - - - -
7 changed files:
- compiler/GHC/Prelude.hs
- compiler/GHC/StgToCmm/Ticky.hs
- compiler/GHC/Types/Id.hs
- compiler/GHC/Unit/Types.hs-boot
- compiler/GHC/Utils/Panic.hs
- compiler/GHC/Utils/Trace.hs
- − compiler/GHC/Utils/Trace.hs-boot
Changes:
=====================================
compiler/GHC/Prelude.hs
=====================================
@@ -48,14 +48,5 @@ NoImplicitPrelude. There are two motivations for this:
import GHC.Prelude.Basic as GHC.Prelude
-import {-# SOURCE #-} GHC.Utils.Trace
- ( pprTrace
- , pprTraceM
- , pprTraceWith
- -- , pprTraceDebug
- -- Do *not* boot-export pprTraceDebug, it *must* be importet in a non-boot way
- -- in order to guarantee it's optimized away in non-debug builds.
- , pprSTrace
- , warnPprTrace
- , pprTraceUserWarning
- )
+-- import {-# SOURCE #-} GHC.Utils.Trace
+import GHC.Utils.Trace hiding ( trace )
=====================================
compiler/GHC/StgToCmm/Ticky.hs
=====================================
@@ -154,7 +154,6 @@ import Data.Maybe
import qualified Data.Char
import Control.Monad ( when, unless )
import GHC.Types.Id.Info
-import GHC.Utils.Trace ( pprTraceDebug )
import GHC.StgToCmm.Env (getCgInfo_maybe)
import Data.Coerce (coerce)
import GHC.Utils.Json
=====================================
compiler/GHC/Types/Id.hs
=====================================
@@ -163,7 +163,6 @@ import GHC.Utils.Misc
import GHC.Utils.Outputable
import GHC.Utils.Panic
import GHC.Utils.Panic.Plain
-import GHC.Utils.Trace
import GHC.Stg.InferTags.TagSig
-- infixl so you can say (id `set` a `set` b)
=====================================
compiler/GHC/Unit/Types.hs-boot
=====================================
@@ -2,7 +2,7 @@
module GHC.Unit.Types where
-- No Prelude. See Note [Exporting pprTrace from GHC.Prelude]
-import Language.Haskell.Syntax.Module.Name.Type (ModuleName)
+import Language.Haskell.Syntax.Module.Name (ModuleName)
import Data.Kind (Type)
data UnitId
=====================================
compiler/GHC/Utils/Panic.hs
=====================================
@@ -52,7 +52,7 @@ module GHC.Utils.Panic
)
where
-import GHC.Prelude
+import GHC.Prelude.Basic
import GHC.Stack
import GHC.Utils.Outputable
=====================================
compiler/GHC/Utils/Trace.hs
=====================================
@@ -20,27 +20,8 @@ Since calls to traces should never be performance sensitive it's okay for these
to be source imports/exports. However we still need to make sure that all
transitive imports from Trace.hs-boot do not import GHC.Prelude.
-To get there we make these changes within the transitive dependencies
-of Trace.hs-boot:
-* Import the regular Prelude instead of GHC.Prelude
-* Move data type definitions into their own modules so that we can eventually
- import SDoc without pulling in half of GHC.
-
-The later has the annoying side effect of adding a few harmless orphan instances.
-Since we end up with e.g. FastString in a different module than the module
-defining the logic needed to define it's show instance.
-But that still seems better than adding a ton of .hs-boot files which can
-affect performance. The other alternative would be to use newtypes which carry
-the actual instances. E.g. newtype ShowFastString = SF FastString and define
-instances only on the newtype(s). But that also seems cumbersome.
-
-So I simply accepted the (few) new orphan instances for now.
-
-NB: It can still be beneficial to explicitly import this module when it's
-important that unfoldings are available. This is particularly important for
-pprTraceDebug which we want to optimize away completely in non-debug builds.
-So we don't provide a boot-export for this function to avoid people using it
-accidentally.
+To get there we import the basic GHC.Prelude.Basic prelude instead of GHC.Prelude
+within the transitive dependencies of Trace.hs
-}
import GHC.Prelude.Basic
=====================================
compiler/GHC/Utils/Trace.hs-boot deleted
=====================================
@@ -1,47 +0,0 @@
--- | Tracing utilities
-module GHC.Utils.Trace
- ( pprTrace
- , pprTraceM
- , pprTraceWith
- -- , pprTraceDebug
- -- Do *not* boot-export pprTraceDebug, it *must* be importet in a non-boot way
- -- in order to guarantee it's optimized away in non-debug builds.
- -- , pprTraceIt - Pulling in Outputable just for this seems not worth it.
- , pprTraceException
- , pprSTrace
- , warnPprTrace
- , pprTraceUserWarning
- , trace
- )
-where
-
-import GHC.Prelude.Basic
-
-import GHC.Utils.Outputable ( SDoc )
-import GHC.Utils.Exception ( ExceptionMonad )
-
-import GHC.Stack
-import Debug.Trace (trace)
-
--- | If debug output is on, show some 'SDoc' on the screen
-pprTrace :: String -> SDoc -> a -> a
-
-pprTraceM :: Applicative f => String -> SDoc -> f ()
-
--- | @pprTraceWith desc f x@ is equivalent to @pprTrace desc (f x) x at .
--- This allows you to print details from the returned value as well as from
--- ambient variables.
-pprTraceWith :: String -> (a -> SDoc) -> a -> a
-
-pprTraceException :: ExceptionMonad m => String -> SDoc -> m a -> m a
-
--- | If debug output is on, show some 'SDoc' on the screen along
--- with a call stack when available.
-pprSTrace :: HasCallStack => SDoc -> a -> a
-
--- | Just warn about an assertion failure, recording the given file and line number.
-warnPprTrace :: HasCallStack => Bool -> String -> SDoc -> a -> a
-
--- | For when we want to show the user a non-fatal WARNING so that they can
--- report a GHC bug, but don't want to panic.
-pprTraceUserWarning :: HasCallStack => SDoc -> a -> a
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/963f857c676b364ef35fdbabc45a23ca0a5ee548
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/963f857c676b364ef35fdbabc45a23ca0a5ee548
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/20221102/4516f484/attachment-0001.html>
More information about the ghc-commits
mailing list