{- | This module exposes variations over the standard GHC's logging functions to work with the 'Doc'
     type from the \"pretty\" package. We would like LiquidHaskell to emit diagnostic messages using the very
     same GHC machinery, so that IDE-like programs (e.g. \"ghcid\", \"ghcide\" etc) would be able to
     correctly show errors and warnings to the users, in ther editors.

     Unfortunately, this is not possible to do out of the box because LiquidHaskell uses the 'Doc' type from
     the \"pretty\" package but GHC uses (for historical reasons) its own version. Due to the fact none of
     the constructors are exported, we simply cannot convert between the two types effortlessly, but we have
     to pay the price of a pretty-printing \"roundtrip\".
-}

module Language.Haskell.Liquid.GHC.Logging (
    fromPJDoc
  , putWarnMsg
  , mkLongErrAt
  ) where

import qualified Liquid.GHC.API as GHC
import qualified Text.PrettyPrint.HughesPJ as PJ

-- Unfortunately we need the import below to bring in scope 'PPrint' instances.
import Language.Haskell.Liquid.Types.Errors ()

fromPJDoc :: PJ.Doc -> GHC.SDoc
fromPJDoc :: Doc -> SDoc
fromPJDoc = String -> SDoc
GHC.text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> String
PJ.render

-- | Like the original 'putLogMsg', but internally converts the input 'Doc' (from the \"pretty\" library)
-- into GHC's internal 'SDoc'.
putLogMsg :: GHC.Logger
          -> GHC.DynFlags
          -> GHC.WarnReason
          -> GHC.Severity
          -> GHC.SrcSpan
          -> Maybe GHC.PprStyle
          -> PJ.Doc
          -> IO ()
putLogMsg :: Logger
-> DynFlags
-> WarnReason
-> Severity
-> SrcSpan
-> Maybe PprStyle
-> Doc
-> IO ()
putLogMsg Logger
logger DynFlags
dynFlags WarnReason
reason Severity
sev SrcSpan
srcSpan Maybe PprStyle
_mbStyle =
  Logger -> LogAction
GHC.putLogMsg Logger
logger DynFlags
dynFlags WarnReason
reason Severity
sev SrcSpan
srcSpan forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> SDoc
GHC.text forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> String
PJ.render

defaultErrStyle :: GHC.DynFlags -> GHC.PprStyle
defaultErrStyle :: DynFlags -> PprStyle
defaultErrStyle DynFlags
_dynFlags = PprStyle
GHC.defaultErrStyle

putWarnMsg :: GHC.Logger -> GHC.DynFlags -> GHC.SrcSpan -> PJ.Doc -> IO ()
putWarnMsg :: Logger -> DynFlags -> SrcSpan -> Doc -> IO ()
putWarnMsg Logger
logger DynFlags
dynFlags SrcSpan
srcSpan Doc
doc =
  Logger
-> DynFlags
-> WarnReason
-> Severity
-> SrcSpan
-> Maybe PprStyle
-> Doc
-> IO ()
putLogMsg Logger
logger DynFlags
dynFlags WarnReason
GHC.NoReason Severity
GHC.SevWarning SrcSpan
srcSpan (forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ DynFlags -> PprStyle
defaultErrStyle DynFlags
dynFlags) Doc
doc

-- | Like GHC's 'mkLongErrAt', but it builds the final 'ErrMsg' out of two \"HughesPJ\"'s 'Doc's.
mkLongErrAt :: GHC.SrcSpan -> PJ.Doc -> PJ.Doc -> GHC.TcRn (GHC.MsgEnvelope GHC.DecoratedSDoc)
mkLongErrAt :: SrcSpan -> Doc -> Doc -> TcRn (MsgEnvelope DecoratedSDoc)
mkLongErrAt SrcSpan
srcSpan Doc
msg Doc
extra = SrcSpan -> SDoc -> SDoc -> TcRn (MsgEnvelope DecoratedSDoc)
GHC.mkLongErrAt SrcSpan
srcSpan (Doc -> SDoc
fromPJDoc Doc
msg) (Doc -> SDoc
fromPJDoc Doc
extra)