~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/stdlib/src/gen_fsm.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
-module(gen_fsm).
116
116
-export([behaviour_info/1]).
117
117
 
118
118
%% Internal exports
119
 
-export([init_it/6, print_event/3,
 
119
-export([init_it/6,
120
120
         system_continue/3,
121
121
         system_terminate/4,
122
122
         system_code_change/4,
376
376
        _Msg when Debug =:= [] ->
377
377
            handle_msg(Msg, Parent, Name, StateName, StateData, Mod, Time);
378
378
        _Msg ->
379
 
            Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, 
 
379
            Debug1 = sys:handle_debug(Debug, fun print_event/3,
380
380
                                      {Name, StateName}, {in, Msg}),
381
381
            handle_msg(Msg, Parent, Name, StateName, StateData,
382
382
                       Mod, Time, Debug1)
466
466
    From = from(Msg),
467
467
    case catch dispatch(Msg, Mod, StateName, StateData) of
468
468
        {next_state, NStateName, NStateData} ->
469
 
            Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, 
 
469
            Debug1 = sys:handle_debug(Debug, fun print_event/3,
470
470
                                      {Name, NStateName}, return),
471
471
            loop(Parent, Name, NStateName, NStateData, Mod, infinity, Debug1);
472
472
        {next_state, NStateName, NStateData, Time1} ->
473
 
            Debug1 = sys:handle_debug(Debug, {?MODULE, print_event}, 
 
473
            Debug1 = sys:handle_debug(Debug, fun print_event/3,
474
474
                                      {Name, NStateName}, return),
475
475
            loop(Parent, Name, NStateName, NStateData, Mod, Time1, Debug1);
476
476
        {reply, Reply, NStateName, NStateData} when From =/= undefined ->
519
519
 
520
520
reply(Name, {To, Tag}, Reply, Debug, StateName) ->
521
521
    reply({To, Tag}, Reply),
522
 
    sys:handle_debug(Debug, {?MODULE, print_event}, Name,
 
522
    sys:handle_debug(Debug, fun print_event/3, Name,
523
523
                     {out, Reply, To, StateName}).
524
524
 
525
525
%%% ---------------------------------------------------
542
542
                {shutdown,_}=Shutdown ->
543
543
                    exit(Shutdown);
544
544
                _ ->
545
 
                    error_info(Reason, Name, Msg, StateName, StateData, Debug),
 
545
                    FmtStateData =
 
546
                        case erlang:function_exported(Mod, format_status, 2) of
 
547
                            true ->
 
548
                                Args = [get(), StateData],
 
549
                                case catch Mod:format_status(terminate, Args) of
 
550
                                    {'EXIT', _} -> StateData;
 
551
                                    Else -> Else
 
552
                                end;
 
553
                            _ ->
 
554
                                StateData
 
555
                        end,
 
556
                    error_info(Reason,Name,Msg,StateName,FmtStateData,Debug),
546
557
                    exit(Reason)
547
558
            end
548
559
    end.
603
614
format_status(Opt, StatusData) ->
604
615
    [PDict, SysState, Parent, Debug, [Name, StateName, StateData, Mod, _Time]] =
605
616
        StatusData,
606
 
    Header = lists:concat(["Status for state machine ", Name]),
 
617
    StatusHdr = "Status for state machine",
 
618
    Header = if
 
619
                 is_pid(Name) ->
 
620
                     lists:concat([StatusHdr, " ", pid_to_list(Name)]);
 
621
                 is_atom(Name); is_list(Name) ->
 
622
                     lists:concat([StatusHdr, " ", Name]);
 
623
                 true ->
 
624
                     {StatusHdr, Name}
 
625
             end,
607
626
    Log = sys:get_debug(log, Debug, []),
608
 
    Specfic = 
 
627
    DefaultStatus = [{data, [{"StateData", StateData}]}],
 
628
    Specfic =
609
629
        case erlang:function_exported(Mod, format_status, 2) of
610
630
            true ->
611
631
                case catch Mod:format_status(Opt,[PDict,StateData]) of
612
 
                    {'EXIT', _} -> [{data, [{"StateData", StateData}]}];
613
 
                    Else -> Else
 
632
                    {'EXIT', _} -> DefaultStatus;
 
633
                    StatusList when is_list(StatusList) -> StatusList;
 
634
                    Else -> [Else]
614
635
                end;
615
636
            _ ->
616
 
                [{data, [{"StateData", StateData}]}]
 
637
                DefaultStatus
617
638
        end,
618
639
    [{header, Header},
619
640
     {data, [{"Status", SysState},