[Haskell-cafe] how do FFI calls show up in profiling info?

Ömer Sinan Ağacan omeragacan at gmail.com
Wed Aug 22 07:04:27 UTC 2018


Hi,

Currently foreign calls do not show up in profiles, and the runtime does not
account for time taken by foreign calls when it attributes time costs to cost
centres. For example, if you do something like this:

    foreign import ccall interruptible "block"
        block_interruptible :: IO CInt

    block_wrap :: IO CInt
    block_wrap = block_interruptible

    main = block_wrap >> return ()

With `-prof -fprof-auto` you'll see `block_wrap` in the profile, but the time
field of it will show 0% even though it blocks the whole process during the
whole runtime. This behaviour was reported before in the bug tracker, see [1].
If you need this feature please raise your voice in the ticket so that it can
be considered and prioritized.

For this purpose I'm currently using GHC's event logs and threadscope[2] and
ghc-events-analyze[3]. Example:

    {-# LANGUAGE ForeignFunctionInterface #-}
    {-# LANGUAGE InterruptibleFFI #-}

    module Main where

    import Control.Exception
    import Debug.Trace
    import Foreign.C.Types

    foreign import ccall interruptible "block"
        block_interruptible :: IO CInt

    block_wrap :: IO ()
    block_wrap = do
        traceEventIO "START block"
        (block_interruptible >> return ())
          `finally` traceEventIO "END block"

    main :: IO ()
    main = block_wrap

Compile this with `-eventlog` and run with `+RTS -la`. When you load the
generated eventlog into threadscope you can see the events in "raw events" tab.
Then by clicking to `END block` event you can see the time slice that this
event took, and what other capabilities were doing in the meantime etc.

ghc-events-analyze makes this a bit more useful as it shows one row for each
"window" (see README).

One problem with this though if you're profiling a server then you'll probably
record events for a few minutes, and that'll result in a few GB large eventlog
file, which is currently not loadable using ghc-events (the library both of
these programs use to read eventlog files), see [4] for this. You can play
around with eventlog parameters (see the user manual) to generate less number
of events.

[1]: https://ghc.haskell.org/trac/ghc/ticket/13492#comment:1
[2]: http://hackage.haskell.org/package/threadscope
[3]: Install from git repo to be able to build with newer GHCs:
     https://github.com/well-typed/ghc-events-analyze
[4]: https://github.com/haskell/ghc-events/issues/32

Ömer

Johannes Waldmann <johannes.waldmann at htwk-leipzig.de>, 21 Ağu 2018
Sal, 15:02 tarihinde şunu yazdı:
>
> Dear Cafe,
>
> how would FFI calls show up in profiles?
>
> I am using hmatrix-glpk. The relevant FFI call is in
> https://hackage.haskell.org/package/hmatrix-glpk-0.19.0.0/docs/src/Numeric.LinearProgramming.html#simplexSparse
>
> I am compiling with profiling (for executables and libraries),
> and I am running with +RTS -P .
> The .prof file does not contain  c_simplex_sparse (the C function)
>
> It does mention  simplexSparse (the Haskell function that calls it)
> but with a suspiciously low time.
>
> - J.W.
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.


More information about the Haskell-Cafe mailing list