adding all of botlist, initial add
[botlist.git] / botlistprojects / botsocial / lib / erlang / www_tools / disk_cache.erl
blob65c5990c3583ccb7741814fc7c0a328c06b8ed89
1 -module(disk_cache).
3 %IA Joe Armstrong
4 %ID 970212
5 %IK [disk,cache,key,value]
6 %IH A disk Key-Value cache which uses dets
7 %IT <p><b>disk_cache:start(File)</b> starts a disk cache with the
8 % dets file <b>File</b>. If the file does not exist a new cache is
9 % created. Note Key is single valued.
10 % <p><b>store(Key, Value)</b> inserts a value in the cache.
11 % <p><b>fetch(Key) -> ok{Val} | not_found</b> retrieves a value
12 % <p><b>set_max(int())</b> sets the maximum size of the cache.
13 % <p><b>flush(Key)</b> clears an individual cache item.
14 % <p><b>clear()</b> clers the entire cache.
15 % <p><b>info() -> {Max, [Key]}</b> provides information aboiut the cache.
16 % <p><b>stop()</b> stops the cache.
18 -behaviour(gen_server).
20 %% This is the interface
22 -export([start/1, store/2, fetch/1, flush/1, clear/0, set_max/1, info/0,
23 stop/0]).
25 %% And these are cos we use gen_server
26 -export([init/1, handle_call/3, terminate/2]).
28 -import(lists, [member/2, reverse/1]).
30 -define(SERVER, disk_cache_server).
31 -define(RPC(X), gen_server:call(?SERVER, X, 10000)).
32 -define(DEFAULT_CACHE_ENTRIES, 100).
34 %% start(File) -> ok (creates file if non existent)
35 %% store(Key, Val) -> ok
36 %% fetch(Key) -> {ok, Val} | not_found
37 %% flush(Key) -> ok
38 %% clear() -> ok
39 %% set_max(N) -> ok
40 %% info() -> {File, Max, [Key]}
41 %% stop() -> ok
43 start(F) -> gen_server:start({local,?SERVER},?MODULE,F,[]).
44 store(Key, Val) -> ?RPC({store, Key, Val}).
45 fetch(Key) -> ?RPC({fetch, Key}).
46 flush(Key) -> ?RPC(flush).
47 clear() -> ?RPC(clear).
48 set_max(Max) when integer(Max), Max > 0 -> ?RPC({set_max, Max}).
49 info() -> ?RPC(info).
50 stop() -> ?RPC(stop).
52 %% End Interface
55 init(File) ->
56 io:format("Starting disk cache in file:~p\n", [File]),
57 case dets:open_file(myFile, [{type,set}, {file, File}]) of
58 {ok, Tab} ->
59 Max = get_key_or_default(Tab, max, ?DEFAULT_CACHE_ENTRIES),
60 Keys = get_key_or_default(Tab, keys, []),
61 {ok, {Tab, Max, Keys}};
62 _ ->
63 io:format("Cannot open cache - run make_cache\n",[]),
64 {stop, cannot_open_cache}
65 end.
66 handle_call({store, Key, Val}, _, {Tab, Max, Keys}) ->
67 case member(Key, Keys) of
68 true ->
69 %% remove the old value
70 dets:delete(Tab, {key, Key}),
71 Keys1 = move_to_front(Key, Keys),
72 dets:insert(Tab, {{item,Key},Val}),
73 {reply, ok, {Tab, Max, Keys1}};
74 false ->
75 dets:insert(Tab, {{item,Key},Val}),
76 Keys1 = trim(Tab, [Key|Keys], Max),
77 {reply, ok, {Tab, Max, Keys1}}
78 end;
79 handle_call({fetch, Key}, _, {Tab, Max, Keys}) ->
80 case member(Key, Keys) of
81 true ->
82 Keys1 = move_to_front(Key, Keys),
83 [{_, Val}] = dets:lookup(Tab, {item, Key}),
84 {reply, {ok, Val}, {Tab, Max, Keys1}};
85 false ->
86 {reply, not_found, {Tab, Max, Keys}}
87 end;
88 handle_call({flush, Key}, _, {Tab, Max, Keys}) ->
89 case member(Key, Keys) of
90 true ->
91 Keys1 = remove(Key, Keys),
92 dets:delete(Tab, {item, Key}),
93 {reply, ok, {Tab, Max, Keys1}};
94 false ->
95 {reply, ok, {Tab, Max, Keys}}
96 end;
97 handle_call(clear, _, {Tab, Max, Keys}) ->
98 Keys1 = trim(Tab, Keys, 0),
99 {reply, ok, {Tab, Max, Keys}};
100 handle_call({set_max,N}, _, {Tab, Max, Keys}) ->
101 Keys1 = trim(Tab, Keys, N),
102 {reply, ok, {Tab, N, Keys1}};
103 handle_call(info, _, {Tab, Max, Keys}) ->
104 {reply, {info, Max, Keys}, {Tab, Max, Keys}};
105 handle_call(stop, _, {Tab, Max, Keys}) ->
106 dets:insert(Tab, {max, Max}),
107 dets:insert(Tab, {keys, Keys}),
108 {stop, normal, ok, []}.
110 terminate(normal, _) ->
111 true.
114 get_key_or_default(Tab, Key, Default) ->
115 case dets:lookup(Tab, Key) of
116 [] ->
117 Default;
118 [{_,Val}] ->
120 end.
122 %% trim(Tab, Keys, Max)
123 %% Keys is an ordered list of keys
124 %% If the length of Keys is > max then the list
125 %% is trimmed to Max elements
126 %% and the last elements are removed from the data base
128 trim(Tab, Keys, Max) ->
129 case length(Keys) of
130 N when N > Max ->
131 trim1(N-Max, Tab, reverse(Keys));
132 _ ->
133 Keys
134 end.
136 trim1(0, Tab, Keys) ->
137 reverse(Keys);
138 trim1(N, Tab, [H|T]) ->
139 dets:delete(Tab, {item, H}),
140 trim1(N-1, Tab, T).
142 %% moves H which is *known* to be a member of L to the front of L
144 %% -type move_to_front(A, [A]) -> [A].
146 move_to_front(H, L) -> [H|remove(H,L)].
148 remove(X, [X|T]) -> T;
149 remove(X, [H|T]) -> [H|remove(X, T)].