{-# LANGUAGE CPP #-}
module Control.Super.Plugin.Log
( pprToStr, sDocToStr
, missingCaseError
, smErrMsg, smDebugMsg, smObjMsg, smWarnMsg
, formatGroupSrcSpans
, formatConstraint, formatSpan
, printTrace, printObjTrace, trace
, printObj, printMsg, printErr, printWarn
, pluginAssert, pluginFailSDoc
) where
import Data.List ( groupBy, intercalate )
import Debug.Trace ( trace )
import SrcLoc
( SrcSpan(..)
, srcSpanFileName_maybe
, srcSpanStartLine, srcSpanEndLine
, srcSpanStartCol, srcSpanEndCol )
import Outputable ( Outputable, SDoc )
import FastString ( unpackFS )
import TcRnTypes
( Ct(..), CtFlavour(..)
, ctFlavour, ctPred )
import TcPluginM ( TcPluginM, tcPluginIO, unsafeTcPluginTcM )
import IOEnv ( failWithM )
import Control.Super.Plugin.Debug ( pprToStr, sDocToStr )
import Control.Super.Plugin.Utils ( removeDup )
import Control.Super.Plugin.Constraint ( constraintSourceLocation )
prefixMsg :: String -> String -> String
prefixMsg prefix = unlines . fmap ((pluginMsgPrefix ++ prefix) ++) . lines
pluginMsgPrefix :: String
pluginMsgPrefix = "[SM]"
smErrMsg :: String -> String
smErrMsg = prefixMsg $ " ERROR: "
smWarnMsg :: String -> String
smWarnMsg = prefixMsg $ " WARNING: "
smDebugMsg :: String -> String
smDebugMsg = prefixMsg $ " "
smObjMsg :: String -> String
smObjMsg = prefixMsg $ "> "
missingCaseError :: (Outputable o) => String -> Maybe o -> a
missingCaseError funName (Just val) = error $ "Missing case in '" ++ funName ++ "' for " ++ pprToStr val
missingCaseError funName Nothing = error $ "Missing case in '" ++ funName ++ "'"
formatGroupSrcSpans :: [SrcSpan] -> String
formatGroupSrcSpans spans = unwords $ fmap formatSpanGroup groupedSpans
where
formatSpanGroup :: [SrcSpan] -> String
formatSpanGroup [] = ""
formatSpanGroup ss@(s:_) =
case srcSpanFileName_maybe s of
Nothing -> intercalate ", " $ fmap formatSpan ss
Just file -> unpackFS file ++ ": " ++ intercalate ", " (fmap formatSpan ss) ++ ";"
groupedSpans = groupBy eqFileName $ removeDup spans
eqFileName s1 s2 = srcSpanFileName_maybe s1 == srcSpanFileName_maybe s2
formatSpan :: SrcSpan -> String
formatSpan (UnhelpfulSpan str) = unpackFS str
formatSpan (RealSrcSpan s) =
show (srcSpanStartLine s) ++ ":" ++
show (srcSpanStartCol s) ++ "-" ++
(if srcSpanStartLine s /= srcSpanEndLine s then show (srcSpanEndLine s) ++ ":" else "") ++
show (srcSpanEndCol s)
formatConstraint :: Ct -> String
formatConstraint ct
= "[" ++ formatCtFlavour ct
++ "] " ++ formatCtType ct
++ " (" ++ formatSpan (constraintSourceLocation ct)
++ ", " ++ formatCtDataCon ct
++ ")"
where
formatCtDataCon :: Ct -> String
formatCtDataCon c = case c of
CDictCan {} -> "CDictCan"
#if MIN_VERSION_GLASGOW_HASKELL(8,4,0,0)
CIrredCan {} -> "CIrredCan"
#else
CIrredEvCan {} -> "CIrredEvCan"
#endif
CTyEqCan {} -> "CTyEqCan"
CFunEqCan {} -> "CFunEqCan"
CNonCanonical {} -> "CNonCanonical"
CHoleCan {} -> "CHoleCan"
formatCtFlavour :: Ct -> String
formatCtFlavour c = case ctFlavour c of
Given -> "G"
Wanted {} -> "W"
Derived -> "D"
formatCtType :: Ct -> String
formatCtType c = pprToStr $ ctPred c
printTrace :: (Show a) => a -> a
printTrace x = trace (show x) x
printObjTrace :: (Outputable o) => o -> o
printObjTrace o = trace (pprToStr o) o
internalPrint :: String -> TcPluginM ()
internalPrint = tcPluginIO . putStr
printMsg :: String -> TcPluginM ()
printMsg = internalPrint . smDebugMsg
printErr :: String -> TcPluginM ()
printErr = internalPrint . smErrMsg
printWarn :: String -> TcPluginM ()
printWarn = internalPrint . smWarnMsg
printObj :: Outputable o => o -> TcPluginM ()
printObj = internalPrint . smObjMsg . pprToStr
pluginFailSDoc :: SDoc -> TcPluginM a
pluginFailSDoc msg = do
printMsg $ sDocToStr msg
unsafeTcPluginTcM $ failWithM (sDocToStr msg)
pluginAssert :: Bool -> SDoc -> TcPluginM ()
pluginAssert True _ = return ()
pluginAssert False msg = pluginFailSDoc msg