I have updated the micro-benchmark code to support hashtables and these are the results (for version 8.3.4-11-g1db629e24):
However, the hastable numbers are  skewed because I couldn’t use forall/2 and had to use a manual loop due to the backtracking nature of the hashtable library.  The real numbers are probably better.
Micro-Benchmark code
:- dynamic keydb/2,
           trie/1,
	   consult_db/2,
	   consult_file/1,
	   hashtable/1,
	   db_bench/2.
:- use_module(library(assoc)).
:- use_module(library(apply_macros)).
go :-
   writeln('Database raw and crude micro benchmark'),
   N = 1 000 000,
   format('   -> Testing ~:d entries~n',[N]),
   retractall(db_bench(_,_)),
   test_db(rec,N),
   test_db(nb,N),
   test_db(asrt,N),
   test_db(consult,N),
   test_db(trie,N),
   test_db(hashtable,N),
   print_header(N),
   print_results.
test_db(Name,N) :-
   atomic_list_concat([Name,'_',gen],Gen),
   atomic_list_concat([Name,'_',lookup],Lookup),
   atomic_list_concat([Name,'_',cleanup],Cleanup),
   setup_call_cleanup(
      (  writeln(Gen),
         benchmark_goal( [Name,insert], call(Gen,N))
      ),
      (  writeln(Lookup),
         benchmark_goal( [Name,'1st lookup'], call(Lookup,N)),
         write(Lookup), writeln(' (2nd time)'),
         benchmark_goal( [Name,'2nd lookup'], call(Lookup,N))
      ),
      (  catch( call(Cleanup,N),
                error(existence_error(procedure,_),_),
	        true)
      )
   ) .
                         /**********************
                          *    Db operations   *
                          **********************/
rec_gen(N) :-
   forall(  between(1,N,I),
            (  recordz(I, I)
	    )
   ).
rec_lookup(N) :-
   forall(  between(1,N,I),
            (  recorded(I, I)
	    )
   ).
rec_cleanup(N) :-
   forall(  between(1,N,I),
            (  recorded(I, I, Ref), erase(Ref)
	    )
   ).
nb_gen(N) :-
   forall(  between(1,N,I),
            %(  atom_number(A,I), nb_setval(A, I)
            (  nb_setval('500', I)
	    )
   ).
nb_lookup(N) :-
   forall(  between(1,N,_),
            (  nb_getval('500', _)
	    )
   ).
nb_cleanup(_) :-
   nb_delete('500').
asrt_gen(N) :-
   %retractall(keydb(_,_)),
   forall(  between(1,N,I),
            (  assertz(keydb(I,I))
	    )
   ).
asrt_lookup(N) :-
   forall(  between(1,N,I),
            (  keydb(I,I)
	    )
   ).
asrt_cleanup(_) :-
   retractall(keydb(_,_)).
trie_gen(N) :-
   trie_new(Trie),
   assertz(trie(Trie)),
   forall(  between(1,N,I),
            (  trie_insert(Trie,I,I)
	    )
   ).
trie_lookup(N) :-
   trie(Trie),
   forall(  between(1,N,I),
            (  trie_lookup(Trie,I,I)
	    )
   ).
trie_cleanup(_) :-
   trie(Trie),
   trie_destroy(Trie),
   retractall(trie(_)).
consult_gen(N) :-
   File = '/tmp/consult_db.db_bench',
   assertz(consult_file(File)),
   setup_call_cleanup(
      open(File,write,Stream),
      consult_write_terms(Stream,N),
      close(Stream)
   ),
   load_files([File]).
consult_write_terms(Stream,N) :-
   forall(  between(1,N,I),
            (  format(Stream,'~w.~n',[consult_db(I,I)])
	    )
   ).
consult_lookup(N) :-
   forall(  between(1,N,I),
            (  consult_db(I,I)
	    )
   ).
consult_cleanup(_) :-
   consult_file(F),
   retractall(consult_file(_)),
   delete_file(F).
hashtable_gen(N) :-
   ht_new(HT),
   loop( ht_put1(HT), N),
   assertz(hashtable(HT)).
hashtable_lookup(N) :-
   hashtable(HT),
   loop( ht_get1(HT), N).
hashtable_cleanup(N) :-
   hashtable(HT),
   loop( ht_del1(HT), N),
   retractall(hashtable(_)).
ht_put1(HT,I) :-
   ht_put(HT,I,I).
ht_get1(HT,I) :-
   ht_get(HT,I,I).
ht_del1(HT,I) :-
   ht_del(HT,I,I).
loop(_,0) :- !.
loop(Goal,N) :-
   N > 0,
   call(Goal,N),
   N1 is N - 1,
   loop(Goal,N1).
                         /**********************
                          *    Nice printout   *
                          **********************/
print_header(N) :-
   nl,
   format('~t~w~t~59|~n',['Database raw and crude micro benchmark']),
   format('~t~:d entries~t~59|~n',[N]),
   format('~w ~t~10|~w ~t~12+~t~48| ~w~n',['Database','Operation','Wall time']),
   format('~w ~t~10|~w ~t~12+~t~48| ~w',  ['--------','---------','---------']).
print_results :-
   bagof( b(Db,W),
          S^(db_bench([Db,Type|_], S), get_dict(wall_time,S,W)),
	  Res),
   sort(2,'@<',Res,Sorted),
   nl,
   maplist( {Type}/[b(Db,Wall)]>>
            format('~w ~t~10|~w ~t~12+~`.t~48| ~3f secs.~n',[Db,Type,Wall]),
            Sorted),
   fail.
print_results.
                            /****************
                             *    Helpers   *
                             ****************/
% Measure, print and store wall and cpu time
% used by Goal.
benchmark_goal(BenchMark,Goal) :-
   get_time(OldWall),
   statistics(cputime, OldCpu),
   call(Goal),
   get_time(NewWall),
   statistics(cputime, NewCpu),
   UsedWall is NewWall - OldWall,
   UsedCpu  is NewCpu  - OldCpu,
   assertz( db_bench(BenchMark, stat{  cpu_time: UsedCpu,
                                       wall_time: UsedWall })),
   print_message(information, bench(UsedCpu, UsedWall)).
prolog:message(bench(Cpu, Wall)) -->
   { Perc is round(Cpu*100/Wall) },
   [ '~3f CPU in ~3f seconds (~w% CPU)' - [Cpu, Wall, Perc] ].