{-# LANGUAGE CPP #-}
-- | This module provides a stable interface to access GHC's info provenance information.
-- This is helpful for seeing metadata about heap objects.
module GHC.InfoProv.Compat
  ( InfoProv(..)
  , whereFrom
  ) where

#if MIN_VERSION_base(4,18,0)
import GHC.InfoProv (InfoProv(..), whereFrom)
#elif MIN_VERSION_base(4,17,0)
import qualified GHC.Stack.CCS as CCS

data InfoProv = InfoProv {
  InfoProv -> String
ipName :: String,
  InfoProv -> String
ipDesc :: String,
  InfoProv -> String
ipTyDesc :: String,
  InfoProv -> String
ipLabel :: String,
  InfoProv -> String
ipMod :: String,
  InfoProv -> String
ipSrcFile :: String,
  InfoProv -> String
ipSrcSpan :: String
} deriving (InfoProv -> InfoProv -> Bool
(InfoProv -> InfoProv -> Bool)
-> (InfoProv -> InfoProv -> Bool) -> Eq InfoProv
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InfoProv -> InfoProv -> Bool
== :: InfoProv -> InfoProv -> Bool
$c/= :: InfoProv -> InfoProv -> Bool
/= :: InfoProv -> InfoProv -> Bool
Eq, Int -> InfoProv -> ShowS
[InfoProv] -> ShowS
InfoProv -> String
(Int -> InfoProv -> ShowS)
-> (InfoProv -> String) -> ([InfoProv] -> ShowS) -> Show InfoProv
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> InfoProv -> ShowS
showsPrec :: Int -> InfoProv -> ShowS
$cshow :: InfoProv -> String
show :: InfoProv -> String
$cshowList :: [InfoProv] -> ShowS
showList :: [InfoProv] -> ShowS
Show)


-- | Get information about where a value originated from.
--
-- This information is stored statically in a binary when @super-duper@ is enabled.
-- The source positions will be greatly improved by also enabled debug information with @-g3@.
-- Finally you can enable @-fdistinct-constructor-tables@ to get more precise information about data constructor allocations.
--
-- The information is collect by looking at the info table address of a specific closure and then consulting a specially generated map (by @-finfo-table-map@)
-- to find out where we think the best source position to describe that info table arose from.
whereFrom :: a -> IO (Maybe InfoProv)
whereFrom :: forall a. a -> IO (Maybe InfoProv)
whereFrom a
v = do
  Maybe InfoProv
xs <- a -> IO (Maybe InfoProv)
forall a. a -> IO (Maybe InfoProv)
CCS.whereFrom a
v
  Maybe InfoProv -> IO (Maybe InfoProv)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe InfoProv -> IO (Maybe InfoProv))
-> Maybe InfoProv -> IO (Maybe InfoProv)
forall a b. (a -> b) -> a -> b
$ do
    InfoProv
ip <- Maybe InfoProv
xs
    -- srcFileSpan has the format: `test/Spec.hs:12:1-11`
    (String
srcFile, Char
_:String
srcSpan) <- (String, String) -> Maybe (String, String)
forall a. a -> Maybe a
Just ((String, String) -> Maybe (String, String))
-> (String -> (String, String)) -> String -> Maybe (String, String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Bool) -> String -> (String, String)
forall a. (a -> Bool) -> [a] -> ([a], [a])
break (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
':') (String -> Maybe (String, String))
-> String -> Maybe (String, String)
forall a b. (a -> b) -> a -> b
$ InfoProv -> String
CCS.ipLoc InfoProv
ip
    InfoProv -> Maybe InfoProv
forall a. a -> Maybe a
Just (InfoProv -> Maybe InfoProv) -> InfoProv -> Maybe InfoProv
forall a b. (a -> b) -> a -> b
$
      InfoProv
       { ipName :: String
ipName = InfoProv -> String
CCS.ipName InfoProv
ip
       , ipDesc :: String
ipDesc = InfoProv -> String
CCS.ipDesc InfoProv
ip
       , ipTyDesc :: String
ipTyDesc = InfoProv -> String
CCS.ipTyDesc InfoProv
ip
       , ipLabel :: String
ipLabel = InfoProv -> String
CCS.ipLabel InfoProv
ip
       , ipMod :: String
ipMod = InfoProv -> String
CCS.ipMod InfoProv
ip
       -- the following fields are not available in this version of base
       , ipSrcFile :: String
ipSrcFile = String
srcFile
       , ipSrcSpan :: String
ipSrcSpan = String
srcSpan
       }
#else
import qualified GHC.Stack.CCS as CCS

data InfoProv = InfoProv {
  ipName :: String,
  ipDesc :: String,
  ipTyDesc :: String,
  ipLabel :: String,
  ipMod :: String,
  ipSrcFile :: String,
  ipSrcSpan :: String
} deriving (Eq, Show)


-- | Get information about where a value originated from.
--
-- This information is stored statically in a binary when @super-duper@ is enabled.
-- The source positions will be greatly improved by also enabled debug information with @-g3@.
-- Finally you can enable @-fdistinct-constructor-tables@ to get more precise information about data constructor allocations.
--
-- The information is collect by looking at the info table address of a specific closure and then consulting a specially generated map (by @-finfo-table-map@)
-- to find out where we think the best source position to describe that info table arose from.
whereFrom :: a -> IO (Maybe InfoProv)
whereFrom v = do
  xs <- CCS.whereFrom v
  pure $ do
    [name, desc, tyDesc, label, modName, srcFileSpan] <- Just xs
    -- srcFileSpan has the format: `test/Spec.hs:12:1-11`
    (srcFile, _:srcSpan) <- Just $ break (== ':') srcFileSpan
    Just $
      InfoProv
       { ipName = name
       , ipDesc = desc
       , ipTyDesc = tyDesc
       , ipLabel = label
       , ipMod = modName
       , ipSrcFile = srcFile
       , ipSrcSpan = srcSpan
       }
#endif