... |
... |
@@ -72,6 +72,7 @@ module GHC.Types.Error |
72
|
72
|
, pprMessageBag
|
73
|
73
|
, mkLocMessage
|
74
|
74
|
, mkLocMessageWarningGroups
|
|
75
|
+ , formatDiagnostic
|
75
|
76
|
, getCaretDiagnostic
|
76
|
77
|
|
77
|
78
|
, jsonDiagnostic
|
... |
... |
@@ -495,11 +496,11 @@ data MessageClass |
495
|
496
|
-- ^ Diagnostics from the compiler. This constructor is very powerful as
|
496
|
497
|
-- it allows the construction of a 'MessageClass' with a completely
|
497
|
498
|
-- arbitrary permutation of 'Severity' and 'DiagnosticReason'. As such,
|
498
|
|
- -- users are encouraged to use the 'mkMCDiagnostic' smart constructor
|
|
499
|
+ -- users are encouraged to use higher level primitives
|
499
|
500
|
-- instead. Use this constructor directly only if you need to construct
|
500
|
501
|
-- and manipulate diagnostic messages directly, for example inside
|
501
|
502
|
-- 'GHC.Utils.Error'. In all the other circumstances, /especially/ when
|
502
|
|
- -- emitting compiler diagnostics, use the smart constructor.
|
|
503
|
+ -- emitting compiler diagnostics, use higher level primitives.
|
503
|
504
|
--
|
504
|
505
|
-- The @Maybe 'DiagnosticCode'@ field carries a code (if available) for
|
505
|
506
|
-- this diagnostic. If you are creating a message not tied to any
|
... |
... |
@@ -656,32 +657,51 @@ mkLocMessageWarningGroups |
656
|
657
|
-> SrcSpan -- ^ location
|
657
|
658
|
-> SDoc -- ^ message
|
658
|
659
|
-> SDoc
|
659
|
|
- -- Always print the location, even if it is unhelpful. Error messages
|
660
|
|
- -- are supposed to be in a standard format, and one without a location
|
661
|
|
- -- would look strange. Better to say explicitly "<no location info>".
|
662
|
660
|
mkLocMessageWarningGroups show_warn_groups msg_class locn msg
|
663
|
|
- = sdocOption sdocColScheme $ \col_scheme ->
|
664
|
|
- let locn' = sdocOption sdocErrorSpans $ \case
|
665
|
|
- True -> ppr locn
|
666
|
|
- False -> ppr (srcSpanStart locn)
|
667
|
|
-
|
|
661
|
+ = case msg_class of
|
|
662
|
+ MCDiagnostic severity reason code -> formatDiagnostic show_warn_groups locn severity reason code msg
|
|
663
|
+ _ -> sdocOption sdocColScheme $ \col_scheme ->
|
|
664
|
+ let
|
668
|
665
|
msg_colour = getMessageClassColour msg_class col_scheme
|
669
|
|
- col = coloured msg_colour . text
|
670
|
666
|
|
671
|
667
|
msg_title = coloured msg_colour $
|
672
|
668
|
case msg_class of
|
673
|
|
- MCDiagnostic SevError _ _ -> text "error"
|
674
|
|
- MCDiagnostic SevWarning _ _ -> text "warning"
|
675
|
669
|
MCFatal -> text "fatal"
|
676
|
670
|
_ -> empty
|
677
|
671
|
|
|
672
|
+ in formatLocMessageWarningGroups locn msg_title empty empty msg
|
|
673
|
+
|
|
674
|
+formatDiagnostic
|
|
675
|
+ :: Bool -- ^ Print warning groups?
|
|
676
|
+ -> SrcSpan -- ^ location
|
|
677
|
+ -> Severity
|
|
678
|
+ -> ResolvedDiagnosticReason
|
|
679
|
+ -> Maybe DiagnosticCode
|
|
680
|
+ -> SDoc -- ^ message
|
|
681
|
+ -> SDoc
|
|
682
|
+formatDiagnostic show_warn_groups locn severity reason code msg
|
|
683
|
+ = sdocOption sdocColScheme $ \col_scheme ->
|
|
684
|
+ let
|
|
685
|
+ msg_colour :: Col.PprColour
|
|
686
|
+ msg_colour = getSeverityColour severity col_scheme
|
|
687
|
+
|
|
688
|
+ col :: String -> SDoc
|
|
689
|
+ col = coloured msg_colour . text
|
|
690
|
+
|
|
691
|
+ msg_title :: SDoc
|
|
692
|
+ msg_title = coloured msg_colour $
|
|
693
|
+ case severity of
|
|
694
|
+ SevError -> text "error"
|
|
695
|
+ SevWarning -> text "warning"
|
|
696
|
+ SevIgnore -> empty
|
|
697
|
+
|
|
698
|
+ warning_flag_doc :: SDoc
|
678
|
699
|
warning_flag_doc =
|
679
|
|
- case msg_class of
|
680
|
|
- MCDiagnostic sev reason _code
|
681
|
|
- | Just msg <- flag_msg sev (resolvedDiagnosticReason reason)
|
682
|
|
- -> brackets msg
|
683
|
|
- _ -> empty
|
|
700
|
+ case flag_msg severity (resolvedDiagnosticReason reason) of
|
|
701
|
+ Nothing -> empty
|
|
702
|
+ Just msg -> brackets msg
|
684
|
703
|
|
|
704
|
+ ppr_with_hyperlink :: DiagnosticCode -> SDoc
|
685
|
705
|
ppr_with_hyperlink code =
|
686
|
706
|
-- this is a bit hacky, but we assume that if the terminal supports colors
|
687
|
707
|
-- then it should also support links
|
... |
... |
@@ -691,10 +711,11 @@ mkLocMessageWarningGroups show_warn_groups msg_class locn msg |
691
|
711
|
then ppr $ LinkedDiagCode code
|
692
|
712
|
else ppr code
|
693
|
713
|
|
|
714
|
+ code_doc :: SDoc
|
694
|
715
|
code_doc =
|
695
|
|
- case msg_class of
|
696
|
|
- MCDiagnostic _ _ (Just code) -> brackets (ppr_with_hyperlink code)
|
697
|
|
- _ -> empty
|
|
716
|
+ case code of
|
|
717
|
+ Just code -> brackets (ppr_with_hyperlink code)
|
|
718
|
+ Nothing -> empty
|
698
|
719
|
|
699
|
720
|
flag_msg :: Severity -> DiagnosticReason -> Maybe SDoc
|
700
|
721
|
flag_msg SevIgnore _ = Nothing
|
... |
... |
@@ -725,13 +746,35 @@ mkLocMessageWarningGroups show_warn_groups msg_class locn msg |
725
|
746
|
vcat [ text "locn:" <+> ppr locn
|
726
|
747
|
, text "msg:" <+> ppr msg ]
|
727
|
748
|
|
|
749
|
+ warn_flag_grp :: [WarningGroup] -> SDoc
|
728
|
750
|
warn_flag_grp groups
|
729
|
751
|
| show_warn_groups, not (null groups)
|
730
|
752
|
= text $ "(in " ++ intercalate ", " (map (("-W"++) . warningGroupName) groups) ++ ")"
|
731
|
753
|
| otherwise = empty
|
732
|
754
|
|
|
755
|
+ in formatLocMessageWarningGroups locn msg_title code_doc warning_flag_doc msg
|
|
756
|
+
|
|
757
|
+formatLocMessageWarningGroups
|
|
758
|
+ :: SrcSpan -- ^ location
|
|
759
|
+ -> SDoc -- ^ title
|
|
760
|
+ -> SDoc -- ^ diagnostic code
|
|
761
|
+ -> SDoc -- ^ warning groups
|
|
762
|
+ -> SDoc -- ^ message
|
|
763
|
+ -> SDoc
|
|
764
|
+formatLocMessageWarningGroups locn msg_title code_doc warning_flag_doc msg
|
|
765
|
+ = sdocOption sdocColScheme $ \col_scheme ->
|
|
766
|
+ let
|
|
767
|
+ -- Always print the location, even if it is unhelpful. Error messages
|
|
768
|
+ -- are supposed to be in a standard format, and one without a location
|
|
769
|
+ -- would look strange. Better to say explicitly "<no location info>".
|
|
770
|
+ locn' :: SDoc
|
|
771
|
+ locn' = sdocOption sdocErrorSpans $ \case
|
|
772
|
+ True -> ppr locn
|
|
773
|
+ False -> ppr (srcSpanStart locn)
|
|
774
|
+
|
733
|
775
|
-- Add prefixes, like Foo.hs:34: warning:
|
734
|
776
|
-- <the warning message>
|
|
777
|
+ header :: SDoc
|
735
|
778
|
header = locn' <> colon <+>
|
736
|
779
|
msg_title <> colon <+>
|
737
|
780
|
code_doc <+> warning_flag_doc
|
... |
... |
@@ -741,11 +784,16 @@ mkLocMessageWarningGroups show_warn_groups msg_class locn msg |
741
|
784
|
msg)
|
742
|
785
|
|
743
|
786
|
getMessageClassColour :: MessageClass -> Col.Scheme -> Col.PprColour
|
744
|
|
-getMessageClassColour (MCDiagnostic SevError _reason _code) = Col.sError
|
745
|
|
-getMessageClassColour (MCDiagnostic SevWarning _reason _code) = Col.sWarning
|
|
787
|
+getMessageClassColour (MCDiagnostic severity _reason _code) = getSeverityColour severity
|
746
|
788
|
getMessageClassColour MCFatal = Col.sFatal
|
747
|
789
|
getMessageClassColour _ = const mempty
|
748
|
790
|
|
|
791
|
+getSeverityColour :: Severity -> Col.Scheme -> Col.PprColour
|
|
792
|
+getSeverityColour severity = case severity of
|
|
793
|
+ SevError -> Col.sError
|
|
794
|
+ SevWarning -> Col.sWarning
|
|
795
|
+ SevIgnore -> const mempty
|
|
796
|
+
|
749
|
797
|
getCaretDiagnostic :: MessageClass -> SrcSpan -> IO SDoc
|
750
|
798
|
getCaretDiagnostic _ (UnhelpfulSpan _) = pure empty
|
751
|
799
|
getCaretDiagnostic msg_class (RealSrcSpan span _) =
|