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

« back to all changes in this revision

Viewing changes to lib/ssh/src/ssh_math.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
 
 
19
%%% Description: SSH math utilities
 
20
 
 
21
-module(ssh_math).
 
22
 
 
23
-export([ilog2/1, ipow/3, invert/2, ipow2/3]).
 
24
         
 
25
 
 
26
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
27
%%
 
28
%% INTEGER utils
 
29
%%
 
30
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
31
 
 
32
%% number of bits (used) in a integer = isize(N) = |log2(N)|+1
 
33
ilog2(N) ->
 
34
    ssh_bits:isize(N) - 1.
 
35
 
 
36
 
 
37
%% calculate A^B mod M
 
38
ipow(A, B, M) when M > 0, B >= 0 ->
 
39
    crypto:mod_exp(A, B, M).
 
40
 
 
41
ipow2(A, B, M) when M > 0, B >= 0 ->
 
42
    if A == 1 -> 
 
43
            1;
 
44
       true -> 
 
45
            ipow2(A, B, M, 1)
 
46
    end.
 
47
 
 
48
ipow2(A, 1, M, Prod) ->
 
49
    (A*Prod) rem M;
 
50
ipow2(_A, 0, _M, Prod) ->
 
51
    Prod;
 
52
ipow2(A, B, M, Prod)  ->
 
53
    B1 = B bsr 1,
 
54
    A1 = (A*A) rem M,
 
55
    if B - B1 == B1 ->
 
56
            ipow2(A1, B1, M, Prod);
 
57
       true ->
 
58
            ipow2(A1, B1, M, (A*Prod) rem M)
 
59
    end.
 
60
 
 
61
%% %%
 
62
%% %% Normal gcd
 
63
%% %%
 
64
%% gcd(R, Q) when abs(Q) < abs(R) -> gcd1(Q,R);
 
65
%% gcd(R, Q) -> gcd1(R,Q).
 
66
 
 
67
%% gcd1(0, Q) -> Q;
 
68
%% gcd1(R, Q) ->
 
69
%%     gcd1(Q rem R, R).
 
70
 
 
71
 
 
72
%% %%
 
73
%% %% Least common multiple of (R,Q)
 
74
%% %%
 
75
%% lcm(0, _Q) -> 0;
 
76
%% lcm(_R, 0) -> 0;
 
77
%% lcm(R, Q) ->
 
78
%%     (Q div gcd(R, Q)) * R.
 
79
 
 
80
%% %%
 
81
%% %% Extended gcd gcd(R,Q) -> {G, {A,B}} such that G == R*A + Q*B
 
82
%% %%
 
83
%% %% Here we could have use for a bif divrem(Q, R) -> {Quote, Remainder}
 
84
%% %%
 
85
%% egcd(R,Q) when abs(Q) < abs(R) -> egcd1(Q,R,1,0,0,1);
 
86
%% egcd(R,Q) -> egcd1(R,Q,0,1,1,0).
 
87
 
 
88
%% egcd1(0,Q,_,_,Q1,Q2) -> {Q, {Q2,Q1}};
 
89
%% egcd1(R,Q,R1,R2,Q1,Q2) ->
 
90
%%     D = Q div R,
 
91
%%     egcd1(Q rem R, R, Q1-D*R1, Q2-D*R2, R1, R2).
 
92
 
 
93
%%
 
94
%% Invert an element X mod P
 
95
%% Calculated as {1, {A,B}} = egcd(X,P),
 
96
%%   1 == P*A + X*B == X*B (mod P) i.e B is the inverse element
 
97
%%
 
98
%% X > 0, P > 0, X < P   (P should be prime)
 
99
%%
 
100
invert(X,P) when X > 0, P > 0, X < P ->
 
101
    I = inv(X,P,1,0),
 
102
    if 
 
103
        I < 0 -> P + I;
 
104
        true -> I
 
105
    end.
 
106
 
 
107
inv(0,_,_,Q) -> Q;
 
108
inv(X,P,R1,Q1) ->
 
109
    D = P div X,
 
110
    inv(P rem X, X, Q1 - D*R1, R1).
 
111
 
 
112
 
 
113
%% %%
 
114
%% %% Integer square root
 
115
%% %%
 
116
 
 
117
%% isqrt(0) -> 0;
 
118
%% isqrt(1) -> 1;
 
119
%% isqrt(X) when X >= 0 ->
 
120
%%     R = X div 2,
 
121
%%     isqrt(X div R, R, X).
 
122
 
 
123
%% isqrt(Q,R,X) when Q < R ->
 
124
%%     R1 = (R+Q) div 2,
 
125
%%     isqrt(X div R1, R1, X);
 
126
%% isqrt(_, R, _) -> R.
 
127
 
 
128