34
   35:- module(malloc_info,
   36          [
   37          ]).   38:- autoload(library(apply),[maplist/3,partition/4]).   39:- autoload(library(lists),[selectchk/3]).   40:- autoload(library(sgml),[load_xml/3]).   41
   42:- use_foreign_library(foreign(mallocinfo)).
   55:- if(current_predicate('$mallinfo'/1)).   56:- export(mallinfo/1).
   69mallinfo(Info) :-
   70    '$mallinfo'(List),
   71    dict_create(Info, malinfo, List).
   72:- endif.   73
   74:- if(current_predicate('$malloc_info'/1)).   75:- export(malloc_info/1).
   87malloc_info(Info) :-
   88    '$malloc_info'(XML),
   89    setup_call_cleanup(
   90        open_string(XML, In),
   91        load_xml(In, DOM, [space(remove)]),
   92        close(In)),
   93    malloc_dom_prolog(DOM, Info).
   94
   95malloc_dom_prolog([element(malloc, _, DOM)], Info) :-
   96    maplist(malloc_prolog, DOM, List),
   97    partition(is_dict, List, Heaps, Rest),
   98    dict_create(Info, malloc, [heaps:Heaps|Rest]).
   99
  100malloc_prolog(element(heap, [nr=NRA], DOM), Heap) :-
  101    !,
  102    atom_number(NRA, NR),
  103    maplist(heap_prolog, DOM, HeapProperties),
  104    dict_create(Heap, heap, [nr-NR|HeapProperties]).
  105malloc_prolog(Element, Pair) :-
  106    misc_field(Element, Pair).
  107
  108heap_prolog(element(sizes, _, DOM), sizes-Sizes) :-
  109    !,
  110    maplist(chunk_size, DOM, Sizes).
  111heap_prolog(Element, Pair) :-
  112    misc_field(Element, Pair).
  113
  114misc_field(element(Name, Attrs0, []), Key-Value) :-
  115    selectchk(type=Type, Attrs0, Attrs1),
  116    atomic_list_concat([Name, '_', Type], Key),
  117    maplist(attr_value, Attrs1, Attrs),
  118    (   Attrs = [_=Value]
  119    ->  true
  120    ;   dict_create(Value, Name, Attrs)
  121    ).
  122
  123chunk_size(element(size, Attrs0, []), Dict) :-
  124    !,
  125    maplist(attr_value, Attrs0, Attrs),
  126    dict_create(Dict, size, Attrs).
  127chunk_size(element(unsorted, Attrs0, []), Dict) :-
  128    maplist(attr_value, Attrs0, Attrs),
  129    dict_create(Dict, unsorted, Attrs).
  130
  131attr_value(Name=In, Name=Out) :-
  132    atom_number(In, Out),
  133    !.
  134attr_value(Name=In, Name=Out) :-
  135    atom_string(In, Out),
  136    !.
  137
  138:- endif.
 
Memory allocation details
This library is provided if the clib package is compiled on a glibc based system, typically Linux. It provides access to the glibc ptmalloc informational functions for diagnosing memory usage. This library exports
*/