summaryrefslogtreecommitdiff
path: root/compiler/main/ErrUtils.hs-boot
diff options
context:
space:
mode:
Diffstat (limited to 'compiler/main/ErrUtils.hs-boot')
-rw-r--r--compiler/main/ErrUtils.hs-boot30
1 files changed, 27 insertions, 3 deletions
diff --git a/compiler/main/ErrUtils.hs-boot b/compiler/main/ErrUtils.hs-boot
index 6f180af546..a2ba51b304 100644
--- a/compiler/main/ErrUtils.hs-boot
+++ b/compiler/main/ErrUtils.hs-boot
@@ -1,10 +1,33 @@
+{-# LANGUAGE RankNTypes #-}
+
module ErrUtils where
import GhcPrelude
-import Outputable (SDoc, PrintUnqualified )
+import Outputable (SDoc, PprStyle )
import SrcLoc (SrcSpan)
import Json
-import {-# SOURCE #-} DynFlags ( DynFlags, DumpFlag )
+import {-# SOURCE #-} DynFlags ( DynFlags )
+
+type DumpAction = DynFlags -> PprStyle -> DumpOptions -> String
+ -> DumpFormat -> SDoc -> IO ()
+
+type TraceAction = forall a. DynFlags -> String -> SDoc -> a -> a
+
+data DumpOptions = DumpOptions
+ { dumpForcedToFile :: Bool
+ , dumpSuffix :: String
+ }
+
+data DumpFormat
+ = FormatHaskell
+ | FormatCore
+ | FormatSTG
+ | FormatByteCode
+ | FormatCMM
+ | FormatASM
+ | FormatC
+ | FormatLLVM
+ | FormatText
data Severity
= SevOutput
@@ -21,6 +44,7 @@ type MsgDoc = SDoc
mkLocMessage :: Severity -> SrcSpan -> MsgDoc -> MsgDoc
mkLocMessageAnn :: Maybe String -> Severity -> SrcSpan -> MsgDoc -> MsgDoc
getCaretDiagnostic :: Severity -> SrcSpan -> IO MsgDoc
-dumpSDoc :: DynFlags -> PrintUnqualified -> DumpFlag -> String -> SDoc -> IO ()
+defaultDumpAction :: DumpAction
+defaultTraceAction :: TraceAction
instance ToJson Severity