1/*
    2   This file is part of the hashtbl library.
    3
    4   hashtbl is free software; you can redistribute it and/or modify it under
    5   the terms of the GNU LGPL. See README.md for details.
    6 */
    7
    8:- module(tests, [run_all_tests/0]).

Testing utilities for the hashtbl library

author
- Gergö Barany <gergo@tud.at>
license
- LGPL

/

   17:- use_module('../nb_hashtbl').   18:- use_module('../p_hashtbl').
 run_all_tests is det
Run unit tests for the hash table modules, as well as some performance tests.
   24run_all_tests :-
   25    run_tests,
   26    timing_tests.
   27
   28timing_tests :-
   29    timing_test(10_000),
   30    timing_test(15_000),
   31    timing_test(20_000),
   32    timing_test(25_000),
   33    timing_test(30_000),
   34    timing_test(35_000).
   35
   36timing_test(N) :-
   37    nb_timing_test(N),
   38    p_timing_test(N).
   39
   40nb_timing_test(N) :-
   41    format('running ~w~n', [nb_timing_test(N)]),
   42    time(nb_timing_test_(N)).
   43
   44nb_timing_test_(N) :-
   45    empty_nb_hashtbl(T),
   46    \+ (
   47        between(1, N, I),
   48        nb_hashtbl_put(T, I, I),
   49        false
   50    ),
   51    nb_hashtbl_get(T, 42, _).
   52
   53p_timing_test(N) :-
   54    format('running ~w~n', [p_timing_test(N)]),
   55    time(p_timing_test_(N)).
   56
   57p_timing_test_(N) :-
   58    empty_p_hashtbl(T),
   59    p_timing_test_(T, 1, N).
   60
   61p_timing_test_(T, I, N) :-
   62    I < N,
   63    !,
   64    p_hashtbl_put(T, I, I, T1),
   65    I1 is I + 1,
   66    p_timing_test_(T1, I1, N).
   67p_timing_test_(T, N, N) :-
   68    p_hashtbl_get(T, 42, _)