OSDN Git Service

2009-11-30 Thomas Quinot <quinot@adacore.com>
[pf3gnuchains/gcc-fork.git] / gcc / ada / g-sechas.adb
1 ------------------------------------------------------------------------------
2 --                                                                          --
3 --                         GNAT LIBRARY COMPONENTS                          --
4 --                                                                          --
5 --                   G N A T . S E C U R E _ H A S H E S                    --
6 --                                                                          --
7 --                                 B o d y                                  --
8 --                                                                          --
9 --           Copyright (C) 2009, Free Software Foundation, Inc.             --
10 --                                                                          --
11 -- GNAT is free software;  you can  redistribute it  and/or modify it under --
12 -- terms of the  GNU General Public License as published  by the Free Soft- --
13 -- ware  Foundation;  either version 3,  or (at your option) any later ver- --
14 -- sion.  GNAT is distributed in the hope that it will be useful, but WITH- --
15 -- OUT ANY WARRANTY;  without even the  implied warranty of MERCHANTABILITY --
16 -- or FITNESS FOR A PARTICULAR PURPOSE.                                     --
17 --                                                                          --
18 -- As a special exception under Section 7 of GPL version 3, you are granted --
19 -- additional permissions described in the GCC Runtime Library Exception,   --
20 -- version 3.1, as published by the Free Software Foundation.               --
21 --                                                                          --
22 -- You should have received a copy of the GNU General Public License and    --
23 -- a copy of the GCC Runtime Library Exception along with this program;     --
24 -- see the files COPYING3 and COPYING.RUNTIME respectively.  If not, see    --
25 -- <http://www.gnu.org/licenses/>.                                          --
26 --                                                                          --
27 -- GNAT was originally developed  by the GNAT team at  New York University. --
28 -- Extensive contributions were provided by Ada Core Technologies Inc.      --
29 --                                                                          --
30 ------------------------------------------------------------------------------
31
32 with System;     use System;
33 with Interfaces; use Interfaces;
34
35 package body GNAT.Secure_Hashes is
36
37    use Ada.Streams;
38
39    Hex_Digit : constant array (Stream_Element range 0 .. 15) of Character :=
40                  ('0', '1', '2', '3', '4', '5', '6', '7',
41                   '8', '9', 'a', 'b', 'c', 'd', 'e', 'f');
42
43    type Fill_Buffer_Access is
44      access procedure
45        (M     : in out Message_State;
46         S     : String;
47         First : Natural;
48         Last  : out Natural);
49    --  A procedure to transfer data from S, starting at First, into M's block
50    --  buffer until either the block buffer is full or all data from S has been
51    --  consumed.
52
53    procedure Fill_Buffer_Copy
54      (M     : in out Message_State;
55       S     : String;
56       First : Natural;
57       Last  : out Natural);
58    --  Transfer procedure which just copies data from S to M
59
60    procedure Fill_Buffer_Swap
61      (M     : in out Message_State;
62       S     : String;
63       First : Natural;
64       Last  : out Natural);
65    --  Transfer procedure which swaps bytes from S when copying into M. S must
66    --  have even length. Note that the swapping is performed considering pairs
67    --  starting at S'First, even if S'First /= First (that is, if
68    --  First = S'First then the first copied byte is always S (S'First + 1),
69    --  and if First = S'First + 1 then the first copied byte is always
70    --  S (S'First).
71
72    procedure To_String (SEA : Stream_Element_Array; S : out String);
73    --  Return the hexadecimal representation of SEA
74
75    ----------------------
76    -- Fill_Buffer_Copy --
77    ----------------------
78
79    procedure Fill_Buffer_Copy
80      (M     : in out Message_State;
81       S     : String;
82       First : Natural;
83       Last  : out Natural)
84    is
85       Buf_String : String (M.Buffer'Range);
86       for Buf_String'Address use M.Buffer'Address;
87       pragma Import (Ada, Buf_String);
88
89       Length : constant Natural :=
90                  Natural'Min (M.Block_Length - M.Last, S'Last - First + 1);
91
92    begin
93       pragma Assert (Length > 0);
94
95       Buf_String (M.Last + 1 .. M.Last + Length) :=
96         S (First .. First + Length - 1);
97       M.Last := M.Last + Length;
98       Last := First + Length - 1;
99    end Fill_Buffer_Copy;
100
101    ----------------------
102    -- Fill_Buffer_Swap --
103    ----------------------
104
105    procedure Fill_Buffer_Swap
106      (M     : in out Message_State;
107       S     : String;
108       First : Natural;
109       Last  : out Natural)
110    is
111       pragma Assert (S'Length mod 2 = 0);
112       Length : constant Natural :=
113                   Natural'Min (M.Block_Length - M.Last, S'Last - First + 1);
114    begin
115       Last := First;
116       while Last - First < Length loop
117          M.Buffer (M.Last + 1 + Last - First) :=
118            (if (Last - S'First) mod 2 = 0
119             then S (Last + 1)
120             else S (Last - 1));
121          Last := Last + 1;
122       end loop;
123       M.Last := M.Last + Length;
124       Last := First + Length - 1;
125    end Fill_Buffer_Swap;
126
127    ---------------
128    -- To_String --
129    ---------------
130
131    procedure To_String (SEA : Stream_Element_Array; S : out String) is
132       pragma Assert (S'Length = 2 * SEA'Length);
133    begin
134       for J in SEA'Range loop
135          declare
136             S_J : constant Natural := 1 + Natural (J - SEA'First) * 2;
137          begin
138             S (S_J)     := Hex_Digit (SEA (J) / 16);
139             S (S_J + 1) := Hex_Digit (SEA (J) mod 16);
140          end;
141       end loop;
142    end To_String;
143
144    -------
145    -- H --
146    -------
147
148    package body H is
149
150       procedure Update
151         (C           : in out Context;
152          S           : String;
153          Fill_Buffer : Fill_Buffer_Access);
154       --  Internal common routine for all Update procedures
155
156       procedure Final
157         (C         : Context;
158          Hash_Bits : out Ada.Streams.Stream_Element_Array);
159       --  Perform final hashing operations (data padding) and extract the
160       --  (possibly truncated) state of C into Hash_Bits.
161
162       ------------
163       -- Digest --
164       ------------
165
166       function Digest (C : Context) return Message_Digest is
167          Hash_Bits : Stream_Element_Array
168                        (1 .. Stream_Element_Offset (Hash_Length));
169       begin
170          Final (C, Hash_Bits);
171          return MD : Message_Digest do
172             To_String (Hash_Bits, MD);
173          end return;
174       end Digest;
175
176       function Digest (S : String) return Message_Digest is
177          C : Context;
178       begin
179          Update (C, S);
180          return Digest (C);
181       end Digest;
182
183       function Digest (A : Stream_Element_Array) return Message_Digest is
184          C : Context;
185       begin
186          Update (C, A);
187          return Digest (C);
188       end Digest;
189
190       -----------
191       -- Final --
192       -----------
193
194       --  Once a complete message has been processed, it is padded with one
195       --  1 bit followed by enough 0 bits so that the last block is
196       --  2 * Word'Size bits short of being completed. The last 2 * Word'Size
197       --  bits are set to the message size in bits (excluding padding).
198
199       procedure Final
200         (C          : Context;
201          Hash_Bits  : out Stream_Element_Array)
202       is
203          FC : Context := C;
204
205          Zeroes : Natural;
206          --  Number of 0 bytes in padding
207
208          Message_Length : Unsigned_64 := FC.M_State.Length;
209          --  Message length in bytes
210
211          Size_Length : constant Natural :=
212                          2 * Hash_State.Word'Size / 8;
213          --  Length in bytes of the size representation
214
215       begin
216          Zeroes := (Block_Length - 1 - Size_Length - FC.M_State.Last)
217                      mod FC.M_State.Block_Length;
218          declare
219             Pad : String (1 .. 1 + Zeroes + Size_Length) :=
220                     (1 => Character'Val (128), others => ASCII.NUL);
221
222             Index       : Natural;
223             First_Index : Natural;
224
225          begin
226             First_Index := (if Hash_Bit_Order = Low_Order_First
227                             then Pad'Last - Size_Length + 1
228                             else Pad'Last);
229
230             Index := First_Index;
231             while Message_Length > 0 loop
232                if Index = First_Index then
233
234                   --  Message_Length is in bytes, but we need to store it as
235                   --  a bit count).
236
237                   Pad (Index) := Character'Val
238                                    (Shift_Left (Message_Length and 16#1f#, 3));
239                   Message_Length := Shift_Right (Message_Length, 5);
240
241                else
242                   Pad (Index) := Character'Val (Message_Length and 16#ff#);
243                   Message_Length := Shift_Right (Message_Length, 8);
244                end if;
245
246                Index := Index +
247                           (if Hash_Bit_Order = Low_Order_First then 1 else -1);
248             end loop;
249
250             Update (FC, Pad);
251          end;
252
253          pragma Assert (FC.M_State.Last = 0);
254
255          Hash_State.To_Hash (FC.H_State, Hash_Bits);
256       end Final;
257
258       ------------
259       -- Update --
260       ------------
261
262       procedure Update
263         (C           : in out Context;
264          S           : String;
265          Fill_Buffer : Fill_Buffer_Access)
266       is
267          Last : Natural := S'First - 1;
268
269       begin
270          C.M_State.Length := C.M_State.Length + S'Length;
271
272          while Last < S'Last loop
273             Fill_Buffer (C.M_State, S, Last + 1, Last);
274
275             if C.M_State.Last = Block_Length then
276                Transform (C.H_State, C.M_State);
277                C.M_State.Last := 0;
278             end if;
279          end loop;
280
281       end Update;
282
283       ------------
284       -- Update --
285       ------------
286
287       procedure Update (C : in out Context; Input : String) is
288       begin
289          Update (C, Input, Fill_Buffer_Copy'Access);
290       end Update;
291
292       ------------
293       -- Update --
294       ------------
295
296       procedure Update (C : in out Context; Input : Stream_Element_Array) is
297          S : String (1 .. Input'Length);
298          for S'Address use Input'Address;
299          pragma Import (Ada, S);
300       begin
301          Update (C, S, Fill_Buffer_Copy'Access);
302       end Update;
303
304       -----------------
305       -- Wide_Update --
306       -----------------
307
308       procedure Wide_Update (C : in out Context; Input : Wide_String) is
309          S : String (1 .. 2 * Input'Length);
310          for S'Address use Input'Address;
311          pragma Import (Ada, S);
312       begin
313          Update
314            (C, S,
315             (if System.Default_Bit_Order /= Low_Order_First
316              then Fill_Buffer_Swap'Access
317              else Fill_Buffer_Copy'Access));
318       end Wide_Update;
319
320       -----------------
321       -- Wide_Digest --
322       -----------------
323
324       function Wide_Digest (W : Wide_String) return Message_Digest is
325          C : Context;
326       begin
327          Wide_Update (C, W);
328          return Digest (C);
329       end Wide_Digest;
330
331    end H;
332
333    -------------------------
334    -- Hash_Function_State --
335    -------------------------
336
337    package body Hash_Function_State is
338
339       -------------
340       -- To_Hash --
341       -------------
342
343       procedure To_Hash (H : State; H_Bits : out Stream_Element_Array) is
344          Hash_Words : constant Natural := H'Size / Word'Size;
345          Result     : State (1 .. Hash_Words) :=
346                         H (H'Last - Hash_Words + 1 .. H'Last);
347
348          R_SEA : Stream_Element_Array (1 .. Result'Size / 8);
349          for R_SEA'Address use Result'Address;
350          pragma Import (Ada, R_SEA);
351
352       begin
353          if System.Default_Bit_Order /= Hash_Bit_Order then
354             for J in Result'Range loop
355                Swap (Result (J)'Address);
356             end loop;
357          end if;
358
359          --  Return truncated hash
360
361          pragma Assert (H_Bits'Length <= R_SEA'Length);
362          H_Bits := R_SEA (R_SEA'First .. R_SEA'First + H_Bits'Length - 1);
363       end To_Hash;
364
365    end Hash_Function_State;
366
367 end GNAT.Secure_Hashes;