1:- module(registry, [
    2    new/2,              % +Key, +Dict
    3    delete/1,           % +Key
    4    options/2,          % +Key, -Options
    5    connections/2       % +Key, -Options
    6]).

Registry of Plasticsearch instances

author
- Hongxin Liang
license
- Apache License Version 2.0 */
 new(+Key, +Dict) is det
Register a new Plasticsearch instance.
   18new(Key, Dict) :-
   19    mutex_create(_, [alias(Key)]),
   20    build_var_dict(Dict, Vars),
   21    Value = Dict.put(vars, Vars),
   22    debug(registry, 'register a new plasticsearch ~w', [Value]),
   23    recorda(Key, Value).
 delete(+Key) is semidet
Delete a Plasticsearch instance.
   29delete(Key) :-
   30    recorded(Key, Value, Ref),
   31    debug(registry, 'deregister plasticsearch ~w', [Value]),
   32    erase(Ref),
   33    mutex_destroy(Key).
   34
   35build_var_dict(Dict, Vars) :-
   36    Vars0 = _{connections:Dict.hosts, dead_connections:[], dead_count:[]},
   37    (   memberchk(random_selector(false), Dict.options)
   38    ->  Vars = Vars0.put(rr, -1)
   39    ;   Vars = Vars0
   40    ).
 options(+Key, -Options) is semidet
Get options of a Plasticsearch instance.
   46options(Key, Options) :-
   47    with_mutex(Key, (
   48        recorded(Key, Value, _),
   49        Options = Value.options)
   50    ).
 connections(+Key, -Connections) is semidet
Get connections of a Plasticsearch instance.
   56connections(Key, Connections) :-
   57    with_mutex(Key, (
   58        recorded(Key, Value, _),
   59        Connections = Value.vars.connections)
   60    )