~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/wx/api_gen/gen_util.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
22
22
-compile(export_all).
23
23
 
24
24
lowercase([F|R]) when F >= $A, F =< $Z ->   [F+($a-$A)|R];
25
 
lowercase(Str) when list(Str) ->   Str.
 
25
lowercase(Str) when is_list(Str) ->   Str.
26
26
 
27
27
lowercase_all([F|R]) when F >= $A, F =< $Z -> [F+($a-$A)|lowercase_all(R)];
28
28
lowercase_all([F|R])  ->               [F|lowercase_all(R)];
29
29
lowercase_all([]) ->                   [].
30
30
 
31
31
uppercase([F|R]) when F >= $a, F =< $z ->    [F+($A-$a)|R];
32
 
uppercase(Str) when list(Str) ->   Str.
 
32
uppercase(Str) when is_list(Str) ->   Str.
33
33
 
34
34
uppercase_all([F|R]) when F >= $a, F =< $z -> [F+($A-$a)|uppercase_all(R)];
35
35
uppercase_all([A|R]) ->             [A|uppercase_all(R)];
61
61
                    %% os:cmd("touch " ++ File),
62
62
                    ok;
63
63
                Diff ->
64
 
                    io:format("Diff in ~s ~s ~n", [File, Diff]),
65
 
                    case file:rename(File ++ ".temp", File) of
66
 
                        ok -> ok;
67
 
                        _ -> 
68
 
                            io:format("*****  Failed to save file ~p ~n",[File])
69
 
                    end                             
 
64
                    case check_diff(Diff) of
 
65
                        copyright -> %% We ignore copyright changes only
 
66
                            ok = file:delete(File ++ ".temp");
 
67
                        _ ->                
 
68
                            io:format("Diff in ~s~n~s ~n", [File, Diff]),
 
69
                            case file:rename(File ++ ".temp", File) of
 
70
                                ok -> ok;
 
71
                                _ -> 
 
72
                                    io:format("*****  Failed to save file ~p ~n",[File])
 
73
                            end
 
74
                    end
70
75
            end,
71
76
            put(current_file, {closed, File})
72
77
    end.
73
78
 
 
79
 
 
80
check_diff(Diff) ->
 
81
    try 
 
82
        [_,D1,_,D2|Tail] = re:split(Diff, "\n"),
 
83
        case Tail of 
 
84
            [] -> ok;
 
85
            [<<>>] -> ok;
 
86
            _ -> throw(diff)
 
87
        end,
 
88
        <<_, _, "%% Copyright", _/binary>> = D1,
 
89
        <<_, _, "%% Copyright", _/binary>> = D2,
 
90
        copyright
 
91
    catch
 
92
        throw:_ ->  diff;
 
93
        error:{badmatch,_} -> diff
 
94
    end.
 
95
 
74
96
w(Str) ->
75
97
    w(Str, []).
76
98
w(Str,Args) ->
130
152
tokens2([], _Seps, Toks, Cs) ->
131
153
    replace_and_remove([lists:reverse(Cs)|Toks], []).
132
154
 
133
 
replace_and_remove([E|R], Acc) when list(E) -> %% Keep everything that is a word
 
155
replace_and_remove([E|R], Acc) when is_list(E) -> %% Keep everything that is a word
134
156
    replace_and_remove(R, [E|Acc]);
135
157
replace_and_remove([$\n | R], Acc) ->   %% It is semi line oriented so keep eol
136
158
    replace_and_remove(R, [eol|Acc]);