{-# LINE 1 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}------------------------------------------------------------------------------- |-- Module : GHC.ExecutionStack.Internal-- Copyright : (c) The University of Glasgow 2013-2015-- License : see libraries/base/LICENSE---- Maintainer : cvs-ghc@haskell.org-- Stability : internal-- Portability : non-portable (GHC Extensions)---- Internals of the `GHC.ExecutionStack` module---- @since 4.9.0.0-----------------------------------------------------------------------------{-# LANGUAGE MultiWayIf #-}moduleGHC.ExecutionStack.Internal(-- * InternalLocation (..),SrcLoc (..),StackTrace ,stackFrames ,stackDepth ,collectStackTrace ,showStackFrames ,invalidateDebugCache )whereimportControl.Monad (join )importData.Word importForeign.C.Types importForeign.C.String (peekCString ,CString )importForeign.Ptr (Ptr ,nullPtr ,castPtr ,plusPtr ,FunPtr )importForeign.ForeignPtr importForeign.Marshal.Alloc (allocaBytes )importForeign.Storable (Storable (..))importSystem.IO.Unsafe (unsafePerformIO ,unsafeInterleaveIO )-- N.B. See rts/include/rts/Libdw.h for notes on stack representation.-- | A location in the original program source.dataSrcLoc =SrcLoc {SrcLoc -> String
sourceFile ::String ,SrcLoc -> Int
sourceLine ::Int ,SrcLoc -> Int
sourceColumn ::Int }-- | Location information about an address from a backtrace.dataLocation =Location {Location -> String
objectName ::String ,Location -> String
functionName ::String ,Location -> Maybe SrcLoc
srcLoc ::Maybe SrcLoc }-- | A chunk of backtrace framesdataChunk =Chunk {Chunk -> Word
chunkFrames ::!Word ,Chunk -> Ptr Chunk
chunkNext ::!(Ptr Chunk ),Chunk -> Ptr Addr
chunkFirstFrame ::!(Ptr Addr )}-- | The state of the execution stacknewtypeStackTrace =StackTrace (ForeignPtr StackTrace )-- | An addresstypeAddr =Ptr ()withSession ::(ForeignPtr Session ->IO a )->IO (Maybe a )withSession :: forall a. (ForeignPtr Session -> IO a) -> IO (Maybe a)
withSession ForeignPtr Session -> IO a
action =doPtr Session
ptr <-IO (Ptr Session)
libdw_pool_take if|Ptr Session
forall a. Ptr a
nullPtr Ptr Session -> Ptr Session -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Session
ptr ->Maybe a -> IO (Maybe a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe a
forall a. Maybe a
Nothing |Bool
otherwise ->doForeignPtr Session
fptr <-FinalizerPtr Session -> Ptr Session -> IO (ForeignPtr Session)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr Session
libdw_pool_release Ptr Session
ptr a
ret <-ForeignPtr Session -> IO a
action ForeignPtr Session
fptr Maybe a -> IO (Maybe a)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe a -> IO (Maybe a)) -> Maybe a -> IO (Maybe a)
forall a b. (a -> b) -> a -> b
$ a -> Maybe a
forall a. a -> Maybe a
Just a
ret -- | How many stack frames in the given 'StackTrace'stackDepth ::StackTrace ->Int stackDepth :: StackTrace -> Int
stackDepth (StackTrace ForeignPtr StackTrace
fptr )=IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ForeignPtr StackTrace -> (Ptr StackTrace -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr StackTrace
fptr ((Ptr StackTrace -> IO Int) -> IO Int)
-> (Ptr StackTrace -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr StackTrace
ptr ->Word -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word -> Int) -> (Word -> Word) -> Word -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Word
asWord (Word -> Int) -> IO Word -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((\Ptr StackTrace
hsc_ptr ->Ptr StackTrace -> Int -> IO Word
forall b. Ptr b -> Int -> IO Word
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr StackTrace
hsc_ptr Int
0))Ptr StackTrace
ptr {-# LINE 84 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}whereasWord :: Word -> Word
asWord =Word -> Word
forall a. a -> a
id ::Word ->Word peekChunk ::Ptr Chunk ->IO Chunk peekChunk :: Ptr Chunk -> IO Chunk
peekChunk Ptr Chunk
ptr =Word -> Ptr Chunk -> Ptr Addr -> Chunk
Chunk (Word -> Ptr Chunk -> Ptr Addr -> Chunk)
-> IO Word -> IO (Ptr Chunk -> Ptr Addr -> Chunk)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((\Ptr Chunk
hsc_ptr ->Ptr Chunk -> Int -> IO Word
forall b. Ptr b -> Int -> IO Word
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Chunk
hsc_ptr Int
0))Ptr Chunk
ptr {-# LINE 90 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}IO (Ptr Chunk -> Ptr Addr -> Chunk)
-> IO (Ptr Chunk) -> IO (Ptr Addr -> Chunk)
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((\Ptr Chunk
hsc_ptr ->Ptr Chunk -> Int -> IO (Ptr Chunk)
forall b. Ptr b -> Int -> IO (Ptr Chunk)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Chunk
hsc_ptr Int
8))Ptr Chunk
ptr {-# LINE 91 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}IO (Ptr Addr -> Chunk) -> IO (Ptr Addr) -> IO Chunk
forall a b. IO (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Ptr Addr -> IO (Ptr Addr)
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Ptr Any -> Ptr Addr
forall a b. Ptr a -> Ptr b
castPtr (Ptr Any -> Ptr Addr) -> Ptr Any -> Ptr Addr
forall a b. (a -> b) -> a -> b
$ ((\Ptr Chunk
hsc_ptr ->Ptr Chunk
hsc_ptr Ptr Chunk -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
16))Ptr Chunk
ptr ){-# LINE 92 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}-- | Return a list of the chunks of a backtrace, from the outer-most to-- inner-most chunk.chunksList ::StackTrace ->IO [Chunk ]chunksList :: StackTrace -> IO [Chunk]
chunksList (StackTrace ForeignPtr StackTrace
fptr )=ForeignPtr StackTrace
-> (Ptr StackTrace -> IO [Chunk]) -> IO [Chunk]
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr StackTrace
fptr ((Ptr StackTrace -> IO [Chunk]) -> IO [Chunk])
-> (Ptr StackTrace -> IO [Chunk]) -> IO [Chunk]
forall a b. (a -> b) -> a -> b
$ \Ptr StackTrace
ptr ->[Chunk] -> Ptr Chunk -> IO [Chunk]
go [](Ptr Chunk -> IO [Chunk]) -> IO (Ptr Chunk) -> IO [Chunk]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ((\Ptr StackTrace
hsc_ptr ->Ptr StackTrace -> Int -> IO (Ptr Chunk)
forall b. Ptr b -> Int -> IO (Ptr Chunk)
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr StackTrace
hsc_ptr Int
8))Ptr StackTrace
ptr {-# LINE 98 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}wherego :: [Chunk] -> Ptr Chunk -> IO [Chunk]
go [Chunk]
accum Ptr Chunk
ptr |Ptr Chunk
ptr Ptr Chunk -> Ptr Chunk -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Chunk
forall a. Ptr a
nullPtr =[Chunk] -> IO [Chunk]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return [Chunk]
accum |Bool
otherwise =doChunk
chunk <-Ptr Chunk -> IO Chunk
peekChunk Ptr Chunk
ptr [Chunk] -> Ptr Chunk -> IO [Chunk]
go (Chunk
chunk Chunk -> [Chunk] -> [Chunk]
forall a. a -> [a] -> [a]
: [Chunk]
accum )(Chunk -> Ptr Chunk
chunkNext Chunk
chunk )-- | Unpack the given 'Location' in the Haskell representationpeekLocation ::Ptr Location ->IO Location peekLocation :: Ptr Location -> IO Location
peekLocation Ptr Location
ptr =doletpeekCStringPtr ::CString ->IO String peekCStringPtr :: CString -> IO String
peekCStringPtr CString
p |CString
p CString -> CString -> Bool
forall a. Eq a => a -> a -> Bool
/= CString
forall a. Ptr a
nullPtr =CString -> IO String
peekCString (CString -> IO String) -> CString -> IO String
forall a b. (a -> b) -> a -> b
$ CString -> CString
forall a b. Ptr a -> Ptr b
castPtr CString
p |Bool
otherwise =String -> IO String
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return String
""String
objFile <-CString -> IO String
peekCStringPtr (CString -> IO String) -> IO CString -> IO String
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< ((\Ptr Location
hsc_ptr ->Ptr Location -> Int -> IO CString
forall b. Ptr b -> Int -> IO CString
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Location
hsc_ptr Int
0))Ptr Location
ptr {-# LINE 113 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}function<-peekCStringPtr=<<((\hsc_ptr->peekByteOffhsc_ptr8))ptr{-# LINE 114 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}srcFile<-peekCStringPtr=<<((\hsc_ptr->peekByteOffhsc_ptr16))ptr{-# LINE 115 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}lineNo<-((\hsc_ptr->peekByteOffhsc_ptr24))ptr::IOWord32{-# LINE 116 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}colNo<-((\hsc_ptr->peekByteOffhsc_ptr28))ptr::IOWord32{-# LINE 117 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}let_srcLoc|nullsrcFile=Nothing|otherwise=Just$SrcLoc{sourceFile=srcFile,sourceLine=fromIntegrallineNo,sourceColumn=fromIntegralcolNo}Location -> IO Location
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Location {objectName :: String
objectName =String
objFile ,functionName :: String
functionName =String
function ,srcLoc :: Maybe SrcLoc
srcLoc =Maybe SrcLoc
_srcLoc }-- | The size in bytes of a 'locationSize'locationSize ::Int locationSize :: Int
locationSize =(Int
32){-# LINE 131 "libraries/base/GHC/ExecutionStack/Internal.hsc" #-}-- | List the frames of a stack trace.stackFrames ::StackTrace ->Maybe [Location ]stackFrames :: StackTrace -> Maybe [Location]
stackFrames st :: StackTrace
st @(StackTrace ForeignPtr StackTrace
fptr )=IO (Maybe [Location]) -> Maybe [Location]
forall a. IO a -> a
unsafePerformIO (IO (Maybe [Location]) -> Maybe [Location])
-> IO (Maybe [Location]) -> Maybe [Location]
forall a b. (a -> b) -> a -> b
$ (ForeignPtr Session -> IO [Location]) -> IO (Maybe [Location])
forall a. (ForeignPtr Session -> IO a) -> IO (Maybe a)
withSession ((ForeignPtr Session -> IO [Location]) -> IO (Maybe [Location]))
-> (ForeignPtr Session -> IO [Location]) -> IO (Maybe [Location])
forall a b. (a -> b) -> a -> b
$ \ForeignPtr Session
sess ->do[Chunk]
chunks <-StackTrace -> IO [Chunk]
chunksList StackTrace
st ForeignPtr Session -> [Chunk] -> IO [Location]
go ForeignPtr Session
sess ([Chunk] -> [Chunk]
forall a. [a] -> [a]
reverse [Chunk]
chunks )wherego ::ForeignPtr Session ->[Chunk ]->IO [Location ]go :: ForeignPtr Session -> [Chunk] -> IO [Location]
go ForeignPtr Session
_[]=[Location] -> IO [Location]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []go ForeignPtr Session
sess (Chunk
chunk : [Chunk]
chunks )=do[Location]
this <-ForeignPtr Session -> Chunk -> IO [Location]
iterChunk ForeignPtr Session
sess Chunk
chunk [Location]
rest <-IO [Location] -> IO [Location]
forall a. IO a -> IO a
unsafeInterleaveIO (ForeignPtr Session -> [Chunk] -> IO [Location]
go ForeignPtr Session
sess [Chunk]
chunks )[Location] -> IO [Location]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Location]
this [Location] -> [Location] -> [Location]
forall a. [a] -> [a] -> [a]
++ [Location]
rest ){-
 Here we lazily lookup the location information associated with each address
 as this can be rather costly. This does mean, however, that if the set of
 loaded modules changes between the time that we capture the stack and the
 time we reach here, we may end up with nonsense (mostly likely merely
 unknown symbols). I think this is a reasonable price to pay, however, as
 module loading/unloading is a rather rare event.
 Moreover, we stand to gain a great deal by lazy lookups as the stack frames
 may never even be requested, meaning the only effort wasted is the
 collection of the stack frames themselves.
 The only slightly tricky thing here is to ensure that the ForeignPtr
 stays alive until we reach the end.
 -}iterChunk ::ForeignPtr Session ->Chunk ->IO [Location ]iterChunk :: ForeignPtr Session -> Chunk -> IO [Location]
iterChunk ForeignPtr Session
sess Chunk
chunk =Word -> Ptr Addr -> IO [Location]
iterFrames (Chunk -> Word
chunkFrames Chunk
chunk )(Chunk -> Ptr Addr
chunkFirstFrame Chunk
chunk )whereiterFrames ::Word ->Ptr Addr ->IO [Location ]iterFrames :: Word -> Ptr Addr -> IO [Location]
iterFrames Word
0Ptr Addr
_=[Location] -> IO [Location]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return []iterFrames Word
n Ptr Addr
frame =doAddr
pc <-Ptr Addr -> IO Addr
forall a. Storable a => Ptr a -> IO a
peek Ptr Addr
frame ::IO Addr Maybe Location
mframe <-Addr -> IO (Maybe Location)
lookupFrame Addr
pc [Location]
rest <-IO [Location] -> IO [Location]
forall a. IO a -> IO a
unsafeInterleaveIO (Word -> Ptr Addr -> IO [Location]
iterFrames (Word
n Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
1)Ptr Addr
forall a. Ptr a
frame' )[Location] -> IO [Location]
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Location] -> IO [Location]) -> [Location] -> IO [Location]
forall a b. (a -> b) -> a -> b
$ [Location]
-> (Location -> [Location]) -> Maybe Location -> [Location]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [Location]
rest (Location -> [Location] -> [Location]
forall a. a -> [a] -> [a]
: [Location]
rest )Maybe Location
mframe whereframe' :: Ptr b
frame' =Ptr Addr
frame Ptr Addr -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Addr -> Int
forall a. Storable a => a -> Int
sizeOf (Addr
forall a. HasCallStack => a
undefined ::Addr )lookupFrame ::Addr ->IO (Maybe Location )lookupFrame :: Addr -> IO (Maybe Location)
lookupFrame Addr
pc =ForeignPtr StackTrace
-> (Ptr StackTrace -> IO (Maybe Location)) -> IO (Maybe Location)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr StackTrace
fptr ((Ptr StackTrace -> IO (Maybe Location)) -> IO (Maybe Location))
-> (Ptr StackTrace -> IO (Maybe Location)) -> IO (Maybe Location)
forall a b. (a -> b) -> a -> b
$ IO (Maybe Location) -> Ptr StackTrace -> IO (Maybe Location)
forall a b. a -> b -> a
const (IO (Maybe Location) -> Ptr StackTrace -> IO (Maybe Location))
-> IO (Maybe Location) -> Ptr StackTrace -> IO (Maybe Location)
forall a b. (a -> b) -> a -> b
$ Int -> (Ptr Location -> IO (Maybe Location)) -> IO (Maybe Location)
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes Int
locationSize ((Ptr Location -> IO (Maybe Location)) -> IO (Maybe Location))
-> (Ptr Location -> IO (Maybe Location)) -> IO (Maybe Location)
forall a b. (a -> b) -> a -> b
$ \Ptr Location
buf ->doCInt
ret <-ForeignPtr Session -> (Ptr Session -> IO CInt) -> IO CInt
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Session
sess ((Ptr Session -> IO CInt) -> IO CInt)
-> (Ptr Session -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \Ptr Session
sessPtr ->Ptr Session -> Ptr Location -> Addr -> IO CInt
libdw_lookup_location Ptr Session
sessPtr Ptr Location
buf Addr
pc caseCInt
ret ofCInt
0->Location -> Maybe Location
forall a. a -> Maybe a
Just (Location -> Maybe Location) -> IO Location -> IO (Maybe Location)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Location -> IO Location
peekLocation Ptr Location
buf CInt
_->Maybe Location -> IO (Maybe Location)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Location
forall a. Maybe a
Nothing -- | A LibdwSession from the runtime systemdataSession foreignimportccallunsafe"libdwPoolTake"libdw_pool_take ::IO (Ptr Session )foreignimportccallunsafe"&libdwPoolRelease"libdw_pool_release ::FunPtr (Ptr Session ->IO ())foreignimportccallunsafe"libdwPoolClear"libdw_pool_clear ::IO ()foreignimportccallunsafe"libdwLookupLocation"libdw_lookup_location ::Ptr Session ->Ptr Location ->Addr ->IO CInt foreignimportccallunsafe"libdwGetBacktrace"libdw_get_backtrace ::Ptr Session ->IO (Ptr StackTrace )foreignimportccallunsafe"&backtraceFree"backtrace_free ::FunPtr (Ptr StackTrace ->IO ())-- | Get an execution stack.collectStackTrace ::IO (Maybe StackTrace )collectStackTrace :: IO (Maybe StackTrace)
collectStackTrace =(Maybe (Maybe StackTrace) -> Maybe StackTrace)
-> IO (Maybe (Maybe StackTrace)) -> IO (Maybe StackTrace)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Maybe (Maybe StackTrace) -> Maybe StackTrace
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (Maybe (Maybe StackTrace)) -> IO (Maybe StackTrace))
-> IO (Maybe (Maybe StackTrace)) -> IO (Maybe StackTrace)
forall a b. (a -> b) -> a -> b
$ (ForeignPtr Session -> IO (Maybe StackTrace))
-> IO (Maybe (Maybe StackTrace))
forall a. (ForeignPtr Session -> IO a) -> IO (Maybe a)
withSession ((ForeignPtr Session -> IO (Maybe StackTrace))
 -> IO (Maybe (Maybe StackTrace)))
-> (ForeignPtr Session -> IO (Maybe StackTrace))
-> IO (Maybe (Maybe StackTrace))
forall a b. (a -> b) -> a -> b
$ \ForeignPtr Session
sess ->doPtr StackTrace
st <-ForeignPtr Session
-> (Ptr Session -> IO (Ptr StackTrace)) -> IO (Ptr StackTrace)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Session
sess Ptr Session -> IO (Ptr StackTrace)
libdw_get_backtrace if|Ptr StackTrace
st Ptr StackTrace -> Ptr StackTrace -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr StackTrace
forall a. Ptr a
nullPtr ->Maybe StackTrace -> IO (Maybe StackTrace)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe StackTrace
forall a. Maybe a
Nothing |Bool
otherwise ->StackTrace -> Maybe StackTrace
forall a. a -> Maybe a
Just (StackTrace -> Maybe StackTrace)
-> (ForeignPtr StackTrace -> StackTrace)
-> ForeignPtr StackTrace
-> Maybe StackTrace
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignPtr StackTrace -> StackTrace
StackTrace (ForeignPtr StackTrace -> Maybe StackTrace)
-> IO (ForeignPtr StackTrace) -> IO (Maybe StackTrace)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FinalizerPtr StackTrace
-> Ptr StackTrace -> IO (ForeignPtr StackTrace)
forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FinalizerPtr StackTrace
backtrace_free Ptr StackTrace
st -- | Free the cached debug data.invalidateDebugCache ::IO ()invalidateDebugCache :: IO ()
invalidateDebugCache =IO ()
libdw_pool_clear -- | Render a stacktrace as a stringshowStackFrames ::[Location ]->ShowS showStackFrames :: [Location] -> ShowS
showStackFrames [Location]
frames =String -> ShowS
showString String
"Stack trace:\n"ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ShowS -> ShowS -> ShowS) -> ShowS -> [ShowS] -> ShowS
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
(.) ShowS
forall a. a -> a
id ((Location -> ShowS) -> [Location] -> [ShowS]
forall a b. (a -> b) -> [a] -> [b]
map Location -> ShowS
showFrame [Location]
frames )whereshowFrame :: Location -> ShowS
showFrame Location
loc =String -> ShowS
showString String
" "ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Location -> ShowS
showLocation Location
loc ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Char -> ShowS
showChar Char
'\n'-- | Render a 'Location' as a stringshowLocation ::Location ->ShowS showLocation :: Location -> ShowS
showLocation Location
loc =String -> ShowS
showString (Location -> String
functionName Location
loc )ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShowS -> (SrcLoc -> ShowS) -> Maybe SrcLoc -> ShowS
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ShowS
forall a. a -> a
id SrcLoc -> ShowS
showSrcLoc (Location -> Maybe SrcLoc
srcLoc Location
loc )ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
" in "ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (Location -> String
objectName Location
loc )whereshowSrcLoc ::SrcLoc ->ShowS showSrcLoc :: SrcLoc -> ShowS
showSrcLoc SrcLoc
sloc =String -> ShowS
showString String
" ("ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString (SrcLoc -> String
sourceFile SrcLoc
sloc )ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
":"ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Show a => a -> ShowS
shows (SrcLoc -> Int
sourceLine SrcLoc
sloc )ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
"."ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> ShowS
forall a. Show a => a -> ShowS
shows (SrcLoc -> Int
sourceColumn SrcLoc
sloc )ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
")"

AltStyle によって変換されたページ (->オリジナル) /