Skip to content
Snippets Groups Projects
Commit 5700979d authored by Jean-Baptiste Mazon's avatar Jean-Baptiste Mazon Committed by Jean-Baptiste Mazon
Browse files

testsuite: check heap profiles readability by hp2ps

This test requires the following locale to be available: fr_FR.utf8

The Haskell part of the program sets LC_ALL to fr_FR, allocates for a
bit to cause one GC, and outputs a number to make use of the locale
it set up earlier.

The Makefile compiles, runs and checks the Haskell program's output;
verifies that we do have all three cases of localized samples in the
.hp file, and runs hp2ps on it.

This ought to ensure:
* libc locales still working as intended on the user's side
* .hp samples are readable to hp2ps
parent d0eef1ad
No related tags found
No related merge requests found
......@@ -30,3 +30,15 @@ T15897:
"$(TEST_HC)" -prof -fprof-auto -debug -v0 T15897.hs
./T15897 10000000 +RTS -s -hc 2>/dev/null
./T15897 10000000 +RTS -s -hr 2>/dev/null
.PHONY: T17877-locale
T17877-locale:
"$(HSC2HS)" "$@.hsc"
"$(TEST_HC)" $(TEST_HC_OPTS) -rtsopts "$@.hs"
"./$@" +RTS -h
sed -ne '/BEGIN_SAMPLE/,/END_SAMPLE/ p' "$@.hp" | grep -qv _SAMPLE
"$(HP2PS_ABS)" "$@.hp"
# In some locales (e.g. mine is fr_FR), printf format sample times as:
# BEGIN_SAMPLE 0,022049
# which is unreadable to hp2ps:
# hp2ps: prof-locale.hp, line 7, floating point number must follow BEGIN_SAMPLE
{-# LANGUAGE ForeignFunctionInterface #-}
import Control.Exception
import Foreign.C.Types
import Foreign.C.String
import Foreign.C.Error
#include <locale.h>
lcAll = #const LC_ALL
foreign import ccall "locale.h setlocale" c_setlocale :: CInt -> CString -> IO CString
foreign import ccall "stdio.h printf" c_printf :: CString -> CDouble -> IO ()
main = do
throwErrnoIfNull "setlocale" $ withCString "fr_FR.utf8" $ c_setlocale lcAll
-- allocate some junk to get a heap profile
s <- getLine
evaluate $ last $ scanl1 (+) $ map fromEnum $ concat $ replicate 100000 s
-- check 0 (test validity): ensure we got a profile (sed|grep in Makefile)
-- check 1: RTS doesn't override user's locale setting
withCString "%'.3f\n" $ \fmt -> c_printf fmt (read s)
-- check 2: heap profile is readable by hp2ps (hp2ps in Makefile)
3141.592653589793
[1 of 1] Compiling Main ( T17877-locale.hs, T17877-locale.o )
Linking T17877-locale ...
3 141,593
......@@ -151,3 +151,5 @@ test('T15897',
makefile_test, ['T15897'])
test('T17572', [], compile_and_run, [''])
test('T17877-locale', normal, makefile_test, [])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment