{-# LANGUAGE TemplateHaskell #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module TextShow.Trace.Hpc () where
import Prelude ()
import Prelude.Compat
import TextShow (TextShow(..), FromStringShow(..), singleton)
import TextShow.Data.Time ()
import TextShow.TH (deriveTextShow)
import Trace.Hpc.Mix (Mix, BoxLabel, CondBox)
import Trace.Hpc.Tix (Tix, TixModule)
import Trace.Hpc.Util (HpcPos, Hash, fromHpcPos)
instance TextShow HpcPos where
showb :: HpcPos -> Builder
showb HpcPos
hp = case HpcPos -> (Int, Int, Int, Int)
fromHpcPos HpcPos
hp of
(Int
l1, Int
c1, Int
l2, Int
c2) -> Int -> Builder
forall a. TextShow a => a -> Builder
showb Int
l1
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> (Char -> Builder
singleton Char
':' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall a. TextShow a => a -> Builder
showb Int
c1)
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> (Char -> Builder
singleton Char
'-' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall a. TextShow a => a -> Builder
showb Int
l2)
Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> (Char -> Builder
singleton Char
':' Builder -> Builder -> Builder
forall a. Semigroup a => a -> a -> a
<> Int -> Builder
forall a. TextShow a => a -> Builder
showb Int
c2)
{-# INLINE showb #-}
instance TextShow Hash where
showb :: Hash -> Builder
showb = FromStringShow Hash -> Builder
forall a. TextShow a => a -> Builder
showb (FromStringShow Hash -> Builder)
-> (Hash -> FromStringShow Hash) -> Hash -> Builder
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Hash -> FromStringShow Hash
forall a. a -> FromStringShow a
FromStringShow
{-# INLINE showb #-}
$(deriveTextShow ''TixModule)
$(deriveTextShow ''CondBox)
$(deriveTextShow ''BoxLabel)
$(deriveTextShow ''Mix)
$(deriveTextShow ''Tix)