1%%%============================================================================
2%%% Licensed under the Apache License, Version 2.0 (the "License");
3%%% you may not use this file except in compliance with the License.
4%%% You may obtain a copy of the License at
5%%%
6%%% http://www.apache.org/licenses/LICENSE-2.0
7%%%
8%%% Unless required by applicable law or agreed to in writing, software
9%%% distributed under the License is distributed on an "AS IS" BASIS,
10%%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
11%%% See the License for the specific language governing permissions and
12%%% limitations under the License.
13%%%============================================================================
14
15%%% @hidden
16%%% @doc Implements a gen_server that maintains the state of a mocked module.
17%%% The state includes function stubs, call history, etc. Meck starts one such
18%%% process per mocked module.
19-module(meck_proc).
20-behaviour(gen_server).
21
22%% API
23-export([start/2]).
24-export([set_expect/2]).
25-export([delete_expect/4]).
26-export([list_expects/2]).
27-export([get_history/1]).
28-export([wait/6]).
29-export([reset/1]).
30-export([validate/1]).
31-export([stop/1]).
32
33%% To be accessible from generated modules
34-export([get_result_spec/3]).
35-export([add_history_exception/5]).
36-export([add_history/5]).
37-export([invalidate/1]).
38
39%% gen_server callbacks
40-export([init/1]).
41-export([handle_call/3]).
42-export([handle_cast/2]).
43-export([handle_info/2]).
44-export([terminate/2]).
45-export([code_change/3]).
46
47%%%============================================================================
48%%% Definitions
49%%%============================================================================
50
51-ifdef(non_namespaced_types). % For older Erlang versions
52-type meck_dict() :: dict().
53-else.
54-type meck_dict() :: dict:dict().
55-endif.
56
57-record(state, {mod :: atom(),
58                can_expect :: any | [{Mod::atom(), Ari::byte()}],
59                expects :: meck_dict(),
60                valid = true :: boolean(),
61                history = [] :: meck_history:history() | undefined,
62                original :: term(),
63                was_sticky = false :: boolean(),
64                merge_expects = false :: boolean(),
65                passthrough = false :: boolean(),
66                reload :: {Compiler::pid(), {From::pid(), Tag::any()}} |
67                          undefined,
68                trackers = [] :: [tracker()]}).
69
70-record(tracker, {opt_func :: '_' | atom(),
71                  args_matcher :: meck_args_matcher:args_matcher(),
72                  opt_caller_pid :: '_' | pid(),
73                  countdown :: non_neg_integer(),
74                  reply_to :: {Caller::pid(), Tag::any()},
75                  expire_at :: erlang:timestamp()}).
76
77%%%============================================================================
78%%% Types
79%%%============================================================================
80
81-type tracker() :: #tracker{}.
82
83%%%============================================================================
84%%% API
85%%%============================================================================
86
87-spec start(Mod::atom(), Options::[proplists:property()]) -> ok | no_return().
88start(Mod, Options) ->
89    StartFunc = case proplists:is_defined(no_link, Options) of
90                    true  -> start;
91                    false -> start_link
92                end,
93    SpawnOpt = proplists:get_value(spawn_opt, Options, []),
94    case gen_server:StartFunc({local, meck_util:proc_name(Mod)}, ?MODULE,
95                              [Mod, Options], [{spawn_opt, SpawnOpt}]) of
96        {ok, _Pid}      -> ok;
97        {error, Reason} -> erlang:error(Reason, [Mod, Options])
98    end.
99
100-spec get_result_spec(Mod::atom(), Func::atom(), Args::[any()]) ->
101        meck_ret_spec:result_spec() | undefined.
102get_result_spec(Mod, Func, Args) ->
103    gen_server(call, Mod, {get_result_spec, Func, Args}).
104
105-spec set_expect(Mod::atom(), meck_expect:expect()) ->
106        ok | {error, Reason::any()}.
107set_expect(Mod, Expect) ->
108    Proc = meck_util:proc_name(Mod),
109    try
110        gen_server:call(Proc, {set_expect, Expect})
111    catch
112        exit:{noproc, _Details} ->
113            Options = [Mod, [passthrough]],
114            case gen_server:start({local, Proc}, ?MODULE, Options, []) of
115                {ok, Pid} ->
116                    Result = gen_server:call(Proc, {set_expect, Expect}),
117                    true = erlang:link(Pid),
118                    Result;
119                {error, {{undefined_module, Mod}, _StackTrace}} ->
120                    erlang:error({not_mocked, Mod})
121            end
122    end.
123
124-spec delete_expect(Mod::atom(), Func::atom(), Ari::byte(), Force::boolean()) -> ok.
125delete_expect(Mod, Func, Ari, Force) ->
126    gen_server(call, Mod, {delete_expect, Func, Ari, Force}).
127
128-spec list_expects(Mod::atom(), ExcludePassthrough::boolean()) ->
129    [{Mod::atom(), Func::atom(), Ari::byte}].
130list_expects(Mod, ExcludePassthrough) ->
131    gen_server(call, Mod, {list_expects, ExcludePassthrough}).
132
133-spec add_history_exception(
134        Mod::atom(), CallerPid::pid(), Func::atom(), Args::[any()],
135        {Class::error|exit|throw, Reason::any(), StackTrace::any()}) ->
136        ok.
137add_history_exception(Mod, CallerPid, Func, Args, {Class, Reason, StackTrace}) ->
138    gen_server(cast, Mod, {add_history, {CallerPid, {Mod, Func, Args}, Class, Reason, StackTrace}}).
139
140-spec add_history(Mod::atom(), CallerPid::pid(), Func::atom(), Args::[any()],
141                  Result::any()) ->
142        ok.
143add_history(Mod, CallerPid, Func, Args, Result) ->
144    gen_server(cast, Mod, {add_history, {CallerPid, {Mod, Func, Args}, Result}}).
145
146-spec get_history(Mod::atom()) -> meck_history:history().
147get_history(Mod) ->
148    gen_server(call, Mod, get_history).
149
150-spec wait(Mod::atom(),
151           Times::non_neg_integer(),
152           OptFunc::'_' | atom(),
153           meck_args_matcher:args_matcher(),
154           OptCallerPid::'_' | pid(),
155           Timeout::non_neg_integer()) ->
156        ok.
157wait(Mod, Times, OptFunc, ArgsMatcher, OptCallerPid, Timeout) ->
158    EffectiveTimeout = case Timeout of
159                           0 ->
160                               infinity;
161                           _Else ->
162                               Timeout
163                       end,
164    Name = meck_util:proc_name(Mod),
165    try gen_server:call(Name, {wait, Times, OptFunc, ArgsMatcher, OptCallerPid,
166                               Timeout},
167                        EffectiveTimeout)
168    of
169        ok ->
170            ok;
171        {error, timeout} ->
172            erlang:error(timeout)
173    catch
174        exit:{timeout, _Details} ->
175            erlang:error(timeout);
176        exit:_Reason ->
177            erlang:error({not_mocked, Mod})
178    end.
179
180-spec reset(Mod::atom()) -> ok.
181reset(Mod) ->
182    gen_server(call, Mod, reset).
183
184-spec validate(Mod::atom()) -> boolean().
185validate(Mod) ->
186    gen_server(call, Mod, validate).
187
188-spec invalidate(Mod::atom()) -> ok.
189invalidate(Mod) ->
190    gen_server(cast, Mod, invalidate).
191
192-spec stop(Mod::atom()) -> ok.
193stop(Mod) ->
194    gen_server(call, Mod, stop).
195
196%%%============================================================================
197%%% gen_server callbacks
198%%%============================================================================
199
200%% @hidden
201init([Mod, Options]) ->
202    Exports = normal_exports(Mod),
203    WasSticky = case proplists:get_bool(unstick, Options) of
204        true -> {module, Mod} = code:ensure_loaded(Mod),
205            unstick_original(Mod);
206        _    -> false
207    end,
208    NoPassCover = proplists:get_bool(no_passthrough_cover, Options),
209    MergeExpects = proplists:get_bool(merge_expects, Options),
210    EnableOnLoad = proplists:get_bool(enable_on_load, Options),
211    Passthrough = proplists:get_bool(passthrough, Options),
212    Original = backup_original(Mod, Passthrough, NoPassCover, EnableOnLoad),
213    NoHistory = proplists:get_bool(no_history, Options),
214    History = if NoHistory -> undefined; true -> [] end,
215    CanExpect = resolve_can_expect(Mod, Exports, Options),
216    Expects = init_expects(Exports, Options),
217    process_flag(trap_exit, true),
218    try
219        Forms = meck_code_gen:to_forms(Mod, Expects),
220        _Bin = meck_code:compile_and_load_forms(Forms),
221        {ok, #state{mod = Mod,
222                    can_expect = CanExpect,
223                    expects = Expects,
224                    original = Original,
225                    was_sticky = WasSticky,
226                    merge_expects = MergeExpects,
227                    passthrough = Passthrough,
228                    history = History}}
229    catch
230        exit:{error_loading_module, Mod, sticky_directory} ->
231            {stop, {module_is_sticky, Mod}}
232    end.
233
234%% @hidden
235handle_call({get_result_spec, Func, Args}, _From, S) ->
236    {ResultSpec, NewExpects} = do_get_result_spec(S#state.expects, Func, Args),
237    {reply, ResultSpec, S#state{expects = NewExpects}};
238handle_call({set_expect, Expect}, From,
239            S = #state{mod = Mod, expects = Expects, merge_expects = MergeExpects}) ->
240    check_if_being_reloaded(S),
241    FuncAri = {Func, Ari} = meck_expect:func_ari(Expect),
242    case validate_expect(Mod, Func, Ari, S#state.can_expect) of
243        ok ->
244            {NewExpects, CompilerPid} = store_expect(Mod, FuncAri, Expect,
245                                                     Expects, MergeExpects),
246            {noreply, S#state{expects = NewExpects,
247                              reload = {CompilerPid, From}}};
248        {error, Reason} ->
249            {reply, {error, Reason}, S}
250    end;
251handle_call({delete_expect, Func, Ari, Force}, From,
252            S = #state{mod = Mod, expects = Expects,
253                       passthrough = PassThrough}) ->
254    check_if_being_reloaded(S),
255    ErasePassThrough = Force orelse (not PassThrough),
256    {NewExpects, CompilerPid} =
257        do_delete_expect(Mod, {Func, Ari}, Expects, ErasePassThrough),
258    {noreply, S#state{expects = NewExpects,
259                      reload = {CompilerPid, From}}};
260handle_call({list_expects, ExcludePassthrough}, _From, S = #state{mod = Mod, expects = Expects}) ->
261    Result =
262        case ExcludePassthrough of
263            false ->
264                [{Mod, Func, Ari} || {Func, Ari} <- dict:fetch_keys(Expects)];
265            true ->
266                [{Mod, Func, Ari} ||
267                    {{Func, Ari}, Expect} <- dict:to_list(Expects),
268                    not meck_expect:is_passthrough(Expect)]
269        end,
270    {reply, Result, S};
271handle_call(get_history, _From, S = #state{history = undefined}) ->
272    {reply, [], S};
273handle_call(get_history, _From, S) ->
274    {reply, lists:reverse(S#state.history), S};
275handle_call({wait, Times, OptFunc, ArgsMatcher, OptCallerPid, Timeout}, From,
276            S = #state{history = History, trackers = Trackers}) ->
277    case times_called(OptFunc, ArgsMatcher, OptCallerPid, History) of
278        CalledSoFar when CalledSoFar >= Times ->
279            {reply, ok, S};
280        _CalledSoFar when Timeout =:= 0 ->
281            {reply, {error, timeout}, S};
282        CalledSoFar ->
283            Tracker = #tracker{opt_func = OptFunc,
284                               args_matcher = ArgsMatcher,
285                               opt_caller_pid = OptCallerPid,
286                               countdown = Times - CalledSoFar,
287                               reply_to = From,
288                               expire_at = timeout_to_timestamp(Timeout)},
289            {noreply, S#state{trackers = [Tracker | Trackers]}}
290    end;
291handle_call(reset, _From, S) ->
292    {reply, ok, S#state{history = []}};
293handle_call(validate, _From, S) ->
294    {reply, S#state.valid, S};
295handle_call(stop, _From, S) ->
296    {stop, normal, ok, S}.
297
298%% @hidden
299handle_cast(invalidate, S) ->
300    {noreply, S#state{valid = false}};
301handle_cast({add_history, HistoryRecord}, S = #state{history = undefined,
302                                                     trackers = Trackers}) ->
303    UpdTrackers = update_trackers(HistoryRecord, Trackers),
304    {noreply, S#state{trackers = UpdTrackers}};
305handle_cast({add_history, HistoryRecord}, S = #state{history = History,
306                                                     trackers = Trackers}) ->
307    UpdTrackers = update_trackers(HistoryRecord, Trackers),
308    {noreply, S#state{history = [HistoryRecord | History],
309                      trackers = UpdTrackers}};
310handle_cast(_Msg, S)  ->
311    {noreply, S}.
312
313%% @hidden
314handle_info({'EXIT', Pid, _Reason}, S = #state{reload = Reload}) ->
315    case Reload of
316        {Pid, From} ->
317            gen_server:reply(From, ok),
318            {noreply, S#state{reload = undefined}};
319        _ ->
320            {noreply, S}
321    end;
322handle_info(_Info, S) ->
323    {noreply, S}.
324
325%% @hidden
326terminate(_Reason, #state{mod = Mod, original = OriginalState,
327                          was_sticky = WasSticky}) ->
328    BackupCover = export_original_cover(Mod, OriginalState),
329    cleanup(Mod),
330    restore_original(Mod, OriginalState, WasSticky, BackupCover),
331    ok.
332
333%% @hidden
334code_change(_OldVsn, S, _Extra) -> {ok, S}.
335
336%%%============================================================================
337%%% Internal functions
338%%%============================================================================
339
340-spec normal_exports(Mod::atom()) -> [meck_expect:func_ari()] | undefined.
341normal_exports(Mod) ->
342    try
343        [FuncAri || FuncAri = {Func, Ari} <- Mod:module_info(exports),
344            normal == expect_type(Mod, Func, Ari)]
345    catch
346        error:undef -> undefined
347    end.
348
349-spec expect_type(Mod::atom(), Func::atom(), Ari::byte()) ->
350        autogenerated | builtin | normal.
351expect_type(_, module_info, 0) -> autogenerated;
352expect_type(_, module_info, 1) -> autogenerated;
353expect_type(Mod, Func, Ari) ->
354    case erlang:is_builtin(Mod, Func, Ari) of
355        true -> builtin;
356        false -> normal
357    end.
358
359-spec backup_original(Mod::atom(), Passthrough::boolean(), NoPassCover::boolean(), EnableOnLoad::boolean()) ->
360    {Cover:: false |
361             {File::string(), Data::string(), CompiledOptions::[any()]},
362     Binary:: no_binary |
363              no_passthrough_cover |
364              binary()}.
365backup_original(Mod, Passthrough, NoPassCover, EnableOnLoad) ->
366    Cover = get_cover_state(Mod),
367    try
368        Forms0 = meck_code:abstract_code(meck_code:beam_file(Mod)),
369        Forms = meck_code:enable_on_load(Forms0, EnableOnLoad),
370        NewName = meck_util:original_name(Mod),
371        CompileOpts = [debug_info | meck_code:compile_options(meck_code:beam_file(Mod))],
372        Renamed = meck_code:rename_module(Forms, NewName),
373        Binary = meck_code:compile_and_load_forms(Renamed, CompileOpts),
374
375        %% At this point we care about `Binary' if and only if we want
376        %% to recompile it to enable cover on the original module code
377        %% so that we can still collect cover stats on functions that
378        %% have not been mocked.  Below are the different values
379        %% passed back along with `Cover'.
380        %%
381        %% `no_passthrough_cover' - there is no coverage on the
382        %% original module OR passthrough coverage has been disabled
383        %% via the `no_passthrough_cover' option
384        %%
385        %% `no_binary' - something went wrong while trying to compile
386        %% the original module in `backup_original'
387        %%
388        %% Binary - a `binary()' of the compiled code for the original
389        %% module that is being mocked, this needs to be passed around
390        %% so that it can be passed to Cover later.  There is no way
391        %% to use the code server to access this binary without first
392        %% saving it to disk.  Instead, it's passed around as state.
393        Binary2 = if
394            (Cover == false) orelse NoPassCover ->
395                no_passthrough_cover;
396            true ->
397                meck_cover:compile_beam(NewName, Binary),
398                Binary
399        end,
400        {Cover, Binary2}
401    catch
402        throw:{object_code_not_found, _Module} ->
403            {Cover, no_binary}; % TODO: What to do here?
404        throw:no_abstract_code ->
405            case Passthrough of
406                true  -> exit({abstract_code_not_found, Mod});
407                false -> {Cover, no_binary}
408            end
409    end.
410
411-spec get_cover_state(Mod::atom()) ->
412        {File::string(), Data::string(), CompileOptions::[any()]} | false.
413get_cover_state(Mod) ->
414    case cover:is_compiled(Mod) of
415        {file, File} ->
416            OriginalCover = meck_cover:dump_coverdata(Mod),
417            CompileOptions =
418            try
419                meck_code:compile_options(meck_code:beam_file(Mod))
420            catch
421                throw:{object_code_not_found, _Module} -> []
422            end,
423            {File, OriginalCover, CompileOptions};
424        _ ->
425            false
426    end.
427
428-spec resolve_can_expect(Mod::atom(),
429                         Exports::[meck_expect:func_ari()] | undefined,
430                         Options::[proplists:property()]) ->
431        any | [meck_expect:func_ari()].
432resolve_can_expect(Mod, Exports, Options) ->
433    NonStrict = proplists:get_bool(non_strict, Options),
434    case {Exports, NonStrict} of
435        {_, true}      -> any;
436        {undefined, _} -> erlang:error({undefined_module, Mod});
437        _              -> Exports
438    end.
439
440-spec init_expects(Exports::[meck_expect:func_ari()] | undefined,
441                   Options::[proplists:property()]) ->
442        meck_dict().
443init_expects(Exports, Options) ->
444    Passthrough = proplists:get_bool(passthrough, Options),
445    StubAll = proplists:is_defined(stub_all, Options),
446    Expects = case Exports of
447                  undefined ->
448                      [];
449                  Exports when Passthrough ->
450                      [meck_expect:new_passthrough(FuncArity) ||
451                          FuncArity <- Exports];
452                  Exports when StubAll ->
453                      StubRet = case lists:keyfind(stub_all, 1, Options) of
454                                    {stub_all, RetSpec} -> RetSpec;
455                                    _ -> meck:val(ok)
456                                end,
457                      [meck_expect:new_dummy(FuncArity, StubRet) ||
458                          FuncArity <- Exports];
459                  Exports ->
460                      []
461              end,
462    lists:foldl(fun(Expect, D) ->
463                        dict:store(meck_expect:func_ari(Expect), Expect, D)
464                end,
465                dict:new(), Expects).
466
467-spec gen_server(Method:: call | cast, Mod::atom(), Msg::tuple() | atom()) -> any().
468gen_server(Func, Mod, Msg) ->
469    Name = meck_util:proc_name(Mod),
470    try gen_server:Func(Name, Msg)
471    catch exit:_Reason -> erlang:error({not_mocked, Mod}) end.
472
473-spec check_if_being_reloaded(#state{}) -> ok.
474check_if_being_reloaded(#state{reload = undefined}) ->
475    ok;
476check_if_being_reloaded(_S) ->
477    erlang:error(concurrent_reload).
478
479-spec do_get_result_spec(Expects::meck_dict(), Func::atom(), Args::[any()]) ->
480        {meck_ret_spec:result_spec() | undefined, NewExpects::meck_dict()}.
481do_get_result_spec(Expects, Func, Args) ->
482    FuncAri = {Func, erlang:length(Args)},
483    Expect = dict:fetch(FuncAri, Expects),
484    {ResultSpec, NewExpect} = meck_expect:fetch_result(Args, Expect),
485    NewExpects = case NewExpect of
486                     unchanged ->
487                         Expects;
488                     _ ->
489                         dict:store(FuncAri, NewExpect, Expects)
490                 end,
491    {ResultSpec, NewExpects}.
492
493-spec validate_expect(Mod::atom(), Func::atom(), Ari::byte(),
494                      CanExpect::any | [meck_expect:func_ari()]) ->
495        ok | {error, Reason::any()}.
496validate_expect(Mod, Func, Ari, CanExpect) ->
497    case expect_type(Mod, Func, Ari) of
498        autogenerated ->
499            {error, {cannot_mock_autogenerated, {Mod, Func, Ari}}};
500        builtin ->
501            {error, {cannot_mock_builtin, {Mod, Func, Ari}}};
502        normal ->
503            case CanExpect =:= any orelse lists:member({Func, Ari}, CanExpect) of
504                true -> ok;
505                _    -> {error, {undefined_function, {Mod, Func, Ari}}}
506            end
507    end.
508
509-spec store_expect(Mod::atom(), meck_expect:func_ari(),
510                   meck_expect:expect(), Expects::meck_dict(), boolean()) ->
511        {NewExpects::meck_dict(), CompilerPid::pid()}.
512store_expect(Mod, FuncAri, Expect, Expects, true) ->
513    NewExpects = case dict:is_key(FuncAri, Expects) of
514        true ->
515            {FuncAri, ExistingClauses} = dict:fetch(FuncAri, Expects),
516            {FuncAri, NewClauses} = Expect,
517            dict:store(FuncAri, {FuncAri, ExistingClauses ++ NewClauses}, Expects);
518        false -> dict:store(FuncAri, Expect, Expects)
519    end,
520    compile_expects(Mod, NewExpects);
521store_expect(Mod, FuncAri, Expect, Expects, false) ->
522    NewExpects =  dict:store(FuncAri, Expect, Expects),
523    compile_expects(Mod, NewExpects).
524
525-spec do_delete_expect(Mod::atom(), meck_expect:func_ari(),
526                       Expects::meck_dict(), ErasePassThrough::boolean()) ->
527        {NewExpects::meck_dict(), CompilerPid::pid()}.
528do_delete_expect(Mod, FuncAri, Expects, ErasePassThrough) ->
529    NewExpects = case ErasePassThrough of
530                     true  ->
531                         dict:erase(FuncAri, Expects);
532                     false ->
533                         dict:store(FuncAri,
534                                    meck_expect:new_passthrough(FuncAri),
535                                    Expects)
536                 end,
537    compile_expects(Mod, NewExpects).
538
539-spec compile_expects(Mod::atom(), Expects::meck_dict()) ->
540        {NewExpects::meck_dict(), CompilerPid::pid()}.
541compile_expects(Mod, Expects) ->
542    %% If the recompilation is made by the server that executes a module
543    %% no module that is called from meck_code:compile_and_load_forms/2
544    %% can be mocked by meck.
545    CompilerPid =
546        erlang:spawn_link(fun() ->
547                                  Forms = meck_code_gen:to_forms(Mod, Expects),
548                                  meck_code:compile_and_load_forms(Forms)
549                          end),
550    {Expects, CompilerPid}.
551
552restore_original(Mod, {false, _Bin}, WasSticky, _BackupCover) ->
553    restick_original(Mod, WasSticky),
554    ok;
555restore_original(Mod, {{File, OriginalCover, Options}, _Bin}, WasSticky, BackupCover) ->
556    case filename:extension(File) of
557        ".erl" ->
558            {ok, Mod} = cover:compile_module(File, Options);
559        ".beam" ->
560            cover:compile_beam(File)
561    end,
562    restick_original(Mod, WasSticky),
563    if BackupCover =/= undefined ->
564        %% Import the cover data for `<name>_meck_original' but since it was
565        %% modified by `export_original_cover' it will count towards `<name>'.
566        ok = cover:import(BackupCover),
567        ok = file:delete(BackupCover);
568    true -> ok
569    end,
570    ok = cover:import(OriginalCover),
571    ok = file:delete(OriginalCover),
572    ok.
573
574%% @doc Export the cover data for `<name>_meck_original' and modify
575%% the data so it can be imported under `<name>'.
576export_original_cover(Mod, {_, Bin}) when is_binary(Bin) ->
577    OriginalMod = meck_util:original_name(Mod),
578    BackupCover = meck_cover:dump_coverdata(OriginalMod),
579    ok = meck_cover:rename_module(BackupCover, Mod),
580    BackupCover;
581export_original_cover(_, _) ->
582    undefined.
583
584unstick_original(Module) -> unstick_original(Module, code:is_sticky(Module)).
585
586unstick_original(Module, true) -> code:unstick_mod(Module);
587unstick_original(_,_) -> false.
588
589restick_original(Module, true) ->
590    code:stick_mod(Module),
591    {module, Module} = code:ensure_loaded(Module),
592    ok;
593restick_original(_,_) -> ok.
594
595-spec cleanup(Mod::atom()) -> boolean().
596cleanup(Mod) ->
597    code:purge(Mod),
598    code:delete(Mod),
599    code:purge(meck_util:original_name(Mod)),
600    code:delete(meck_util:original_name(Mod)).
601
602-spec times_called(OptFunc::'_' | atom(),
603                   meck_args_matcher:args_matcher(),
604                   OptCallerPid::'_' | pid(),
605                   meck_history:history()) ->
606        non_neg_integer().
607times_called(OptFunc, ArgsMatcher, OptCallerPid, History) ->
608    Filter = meck_history:new_filter(OptCallerPid, OptFunc, ArgsMatcher),
609    lists:foldl(fun(HistoryRec, Acc) ->
610                        case Filter(HistoryRec) of
611                            true ->
612                                Acc + 1;
613                            _Else ->
614                                Acc
615                        end
616                end, 0, History).
617
618-spec update_trackers(meck_history:history_record(), [tracker()]) ->
619        UpdTracker::[tracker()].
620update_trackers(HistoryRecord, Trackers) ->
621    update_trackers(HistoryRecord, Trackers, []).
622
623-spec update_trackers(meck_history:history_record(),
624                      Trackers::[tracker()],
625                      CheckedSoFar::[tracker()]) ->
626        UpdTrackers::[tracker()].
627update_trackers(_HistoryRecord, [], UpdatedSoFar) ->
628    UpdatedSoFar;
629update_trackers(HistoryRecord, [Tracker | Rest], UpdatedSoFar) ->
630    CallerPid = erlang:element(1, HistoryRecord),
631    {_Mod, Func, Args} = erlang:element(2, HistoryRecord),
632    case update_tracker(Func, Args, CallerPid, Tracker) of
633        expired ->
634            update_trackers(HistoryRecord, Rest, UpdatedSoFar);
635        UpdTracker ->
636            update_trackers(HistoryRecord, Rest, [UpdTracker | UpdatedSoFar])
637    end.
638
639
640-spec update_tracker(Func::atom(), Args::[any()], Caller::pid(), tracker()) ->
641        expired |
642        (UpdTracker::tracker()).
643update_tracker(Func, Args, CallerPid,
644               #tracker{opt_func = OptFunc,
645                        args_matcher = ArgsMatcher,
646                        opt_caller_pid = OptCallerPid,
647                        countdown = Countdown,
648                        reply_to = ReplyTo,
649                        expire_at = ExpireAt} = Tracker)
650  when (OptFunc =:= '_' orelse Func =:= OptFunc) andalso
651       (OptCallerPid =:= '_' orelse CallerPid =:= OptCallerPid) ->
652    case meck_args_matcher:match(Args, ArgsMatcher) of
653        false ->
654            Tracker;
655        true ->
656            case is_expired(ExpireAt) of
657                true ->
658                    expired;
659                false when Countdown == 1 ->
660                    gen_server:reply(ReplyTo, ok),
661                    expired;
662                false ->
663                    Tracker#tracker{countdown = Countdown - 1}
664            end
665    end;
666update_tracker(_Func, _Args, _CallerPid, Tracker) ->
667    Tracker.
668
669-spec timeout_to_timestamp(Timeout::non_neg_integer()) -> erlang:timestamp().
670timeout_to_timestamp(Timeout) ->
671    {MacroSecs, Secs, MicroSecs} = os:timestamp(),
672    MicroSecs2 = MicroSecs + Timeout * 1000,
673    UpdMicroSecs = MicroSecs2 rem 1000000,
674    Secs2 = Secs + MicroSecs2 div 1000000,
675    UpdSecs = Secs2 rem 1000000,
676    UpdMacroSecs = MacroSecs + Secs2 div 1000000,
677    {UpdMacroSecs, UpdSecs, UpdMicroSecs}.
678
679-spec is_expired(erlang:timestamp()) -> boolean().
680is_expired({MacroSecs, Secs, MicroSecs}) ->
681    {NowMacroSecs, NowSecs, NowMicroSecs} = os:timestamp(),
682    ((NowMacroSecs > MacroSecs) orelse
683     (NowMacroSecs == MacroSecs andalso NowSecs > Secs) orelse
684     (NowMacroSecs == MacroSecs andalso NowSecs == Secs andalso
685      NowMicroSecs > MicroSecs)).
686