1-- This program is free software; you can redistribute it and/or
2-- modify it under the terms of the GNU General Public License as
3-- published by the Free Software Foundation; either version 2 of the
4-- License, or (at your option) any later version.
5
6-- This program is distributed in the hope that it will be useful,
7-- but WITHOUT ANY WARRANTY; without even the implied warranty of
8-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
9-- General Public License for more details.
10
11-- You should have received a copy of the GNU General Public License
12-- along with this program; if not, write to the Free Software
13-- Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA
14-- 02111-1307, USA.
15
16-- As a special exception, if other files instantiate generics from
17-- this unit, or you link this unit with other files to produce an
18-- executable, this unit does not by itself cause the resulting
19-- executable to be covered by the GNU General Public License. This
20-- exception does not however invalidate any other reasons why the
21-- executable file might be covered by the GNU Public License.
22
23with Ada.Containers.Indefinite_Vectors;
24
25package body Crypto.Symmetric.AE_OCB is
26
27   -- useful constants
28   Zero_Bytes: constant Bytes(0..(Bytes_Per_Block - 1)) := (others => 0);
29   Zero_Block: constant Block := To_Block_Type(Zero_Bytes);
30   -- If Store_Internally = True, every Ciphertext block will be stored in
31   -- the Vector Masked_Plaintext
32   Store_Internally: Boolean := False;
33
34   -- package initializations
35   package Vectors is new Ada.Containers.Indefinite_Vectors(Index_Type   => Positive,
36                                                            Element_Type => Bytes);
37   Masked_Plaintext: Vectors.Vector;
38
39   -----------------------------------------------------------------
40   ----
41   ---- auxiliary functions and procedures
42   ----
43   -----------------------------------------------------------------
44
45   -- This procedure takes out the first element of the Vector
46   -- Masked_Plaintext and deletes it.
47   procedure Read_Masked_Plaintext(B : out Bytes;
48                         Count : out Natural) is
49      use Ada.Containers;
50   begin
51      if Masked_Plaintext.Length = 0 then
52         Count := 0;
53      else
54         if Masked_Plaintext.First_Element'Length = Bytes_Per_Block then
55            B := Masked_Plaintext.First_Element;
56            Count := Bytes_Per_Block;
57         else
58            declare
59               Temp: Bytes := Zero_Bytes;
60            begin
61               Temp(Temp'First..Masked_Plaintext.First_Element'Length-1)
62                 := Masked_Plaintext.First_Element;
63               B := Temp;
64               Count := Masked_Plaintext.First_Element'Length;
65            end;
66         end if;
67         Masked_Plaintext.Delete_First;
68      end if;
69   end Read_Masked_Plaintext;
70
71   -----------------------------------------------------------------
72
73   -- This procedure calculates all needed irreducible polynomials
74   -- and stores them into an array called L_Array.
75   procedure Generate_L(A: in out Block_Array) is
76      Tmp, Prev_L: Bytes := Zero_Bytes;
77   begin
78      BC.Encrypt(Zero_Block, A(0)); -- L(0) := L
79      -- generate L(-1)
80      A(-1) := Shift_Right(A(0), 1);
81      Tmp := To_Bytes(A(-1));
82      Prev_L := To_Bytes(A(0));
83
84      if (Prev_L(Prev_L'Last) and 16#01#) /= 0 then -- LSB of L = 1?
85         if Bytes_Per_Block = 16 then -- message blocksize n = 128 bit
86            Tmp(Tmp'Last) := Tmp(Tmp'Last) xor 16#43#;
87         elsif Bytes_Per_Block = 8 then -- message blocksize n = 64 bit
88            Tmp(Tmp'Last) := Tmp(Tmp'Last) xor 16#0d#;
89         else
90            raise Blocklength_Not_Supported;
91         end if;
92         Tmp(Tmp'First) := Tmp(Tmp'First) xor 16#80#;
93         A(-1) := To_Block_Type(Tmp);
94      end if;
95
96      -- generate L(1..31);
97      for I in 1..A'Last loop
98         A(I) := Shift_Left(A(I-1), 1);
99         Tmp := To_Bytes(A(I));
100         Prev_L := To_Bytes(A(I-1));
101
102         if (Prev_L(Prev_L'First) and 16#80#) /= 0 then -- MSB of Prev_L = 1?
103            if Bytes_Per_Block = 16 then
104               Tmp(Tmp'Last) := Tmp(Tmp'Last) xor 16#87#;
105            elsif Bytes_Per_Block = 8 then
106               Tmp(Tmp'Last) := Tmp(Tmp'Last) xor 16#1b#;
107            else
108               raise Blocklength_Not_Supported;
109            end if;
110            A(I) := To_Block_Type(Tmp);
111         end if;
112      end loop;
113
114   end Generate_L;
115
116   -----------------------------------------------------------------
117
118   -- This function converts the byte-length of the last Ciphertext block
119   -- in the binary representation and returns a Block_Type.
120   function Convert_Length_To_Block(N: in Natural) return Block is
121      B: Bytes := Zero_Bytes;
122      W: constant Word := Word(N);
123      B_Word: constant Byte_Word := To_Byte_Word(W); -- subtype Byte_Word is Bytes (0 .. 3);
124   begin
125      B(B'Last-(B_Word'Length-1)..B'Last) := B_Word;
126      return To_Block_Type(B);
127   end Convert_Length_To_Block;
128
129   -----------------------------------------------------------------
130
131   -- This procedure seperates the last Ciphertext block and the Tag (out of
132   -- one or two blocks).
133   procedure Extract(This       : in     AE_OCB;
134                     A          : in     Bytes;
135                     B          : in     Bytes := Zero_Bytes;
136                     Bytes_Read : in     Natural;  -- Bytes_Read never zero when calling this procedure!
137                     Bitlen     : in out Block;
138                     Bytelen    : out    Natural;
139                     Last_Block : in out Bytes;    -- initialized as Zero_Block
140                     Tag        : in out Bytes;    -- initialited as Zero_Block
141                     Two_Blocks : in     Boolean;
142                     Dec        : out    Boolean) is
143      Overlap: constant Integer := Bytes_Read - This.Taglen;
144   begin
145      Dec := False;
146      if Two_Blocks then
147
148         if Store_Internally then
149            -- both blocks (A and B) must be append to Masked_Plaintext
150            Masked_Plaintext.Append(A);
151            Masked_Plaintext.Append(B);
152         end if;
153         -- A is Ciphertext and within B is the Tag, with T <= BPB
154         if (Bytes_Read - This.Taglen) = 0 then
155            Last_Block := A;
156            Tag(Tag'First..This.Taglen-1) := B(B'First..This.Taglen-1);
157            Bytelen := Bytes_Per_Block;
158            Bitlen := Convert_Length_To_Block(8 * Bytelen);
159
160         -- A contains a part of the Tag
161         elsif (Bytes_Read - This.Taglen) < 0 then
162            Last_Block(Last_Block'First..Bytes_Per_Block-abs(Overlap)-1)
163              := A(A'First..Bytes_Per_Block-abs(Overlap)-1);
164            Tag(Tag'First..abs(Overlap)-1)
165              := A(Bytes_Per_Block-abs(Overlap)..A'Last);
166            Tag(abs(Overlap)..abs(Overlap)+Bytes_Read-1)
167              := B(B'First..B'First+Bytes_Read-1);
168            Bytelen := (Bytes_Per_Block-abs(Overlap));
169            Bitlen := Convert_Length_To_Block(8 * Bytelen);
170
171            -- A is an entire Ciphertext block. B contains the last
172            -- Ciphertext bytes and the Tag, so A must be decrypt.
173         elsif (Bytes_Read - This.Taglen) > 0 then
174            Dec := True;
175            Last_Block(Last_Block'First..Overlap-1) := B(B'First..Overlap-1);
176            Tag(Tag'First..This.Taglen-1) := B(Overlap..Bytes_Read-1);
177            Bytelen := Overlap;
178            Bitlen := Convert_Length_To_Block(8 * Bytelen);
179         end if;
180
181      else
182         if Store_Internally then
183            -- Only block A must be append to Masked_Plaintext
184            Masked_Plaintext.Append(A);
185         end if;
186
187         if Overlap < 0 then
188            raise Constraint_Error with "Invalid Ciphertext";
189         elsif Overlap = 0 then -- no Ciphertext was written (|M| = 0)
190            Tag(Tag'First..This.Taglen-1) := A(A'First..A'First+This.Taglen-1);
191            Bytelen := 0;
192            Bitlen := Convert_Length_To_Block(Bytelen);
193         else
194            Last_Block(Last_Block'First..Last_Block'First+Overlap-1)
195              := A(A'First..A'First+Overlap-1);
196            Tag(Tag'First..Tag'First+This.Taglen-1) := A(Overlap..Bytes_Read-1);
197            Bytelen := Overlap;
198            Bitlen := Convert_Length_To_Block(8 * Bytelen);
199         end if;
200
201      end if;
202   end Extract;
203
204   -----------------------------------------------------------------
205
206   -- This function counts the number of trailing 0-bits in the binary
207   -- representation of "Value" (current number of en- or de-crypted
208   -- blocks, started at 1.
209   function Number_Of_Trailing_Zeros(Value : in Positive) return Natural is
210      C: Natural := 0;
211      X: Word := Word(Value);
212   begin
213      if (X and 16#01#) /= 0 then
214         return C;
215      else
216         C := C + 1;
217         for I in 1..Positive'Size loop
218            X := Shift_Right(X,1);
219            if (X and 16#01#) /= 0 then
220               return C;
221            else
222               C := C + 1;
223            end if;
224         end loop;
225      end if;
226      return C;
227   end Number_Of_Trailing_Zeros;
228
229   -----------------------------------------------------------------
230
231   -- This procedure is called every time a block must be encrypted.
232   -- Also the Offset, Checksum and the number of encrypted blocks
233   -- will be updated. The encrypted block will be written.
234   procedure Aux_Enc (This     :  in     AE_OCB;
235                      Offset   :  in out Block;
236                      Checksum :  in out Block;
237                      Count    :  in out Positive;
238                      Write    :  in     Callback_Writer;
239                      Input    :  in     Block;
240                      Output   :  in out Block) is
241   begin
242      Offset := Offset xor This.L_Array(Number_Of_Trailing_Zeros(Count));
243      BC.Encrypt(Input xor Offset, Output);
244      Output := Output xor Offset;
245      Write(To_Bytes(Output));
246      Checksum := Checksum xor Input;
247      Count := Count + 1;
248   end Aux_Enc;
249
250   -----------------------------------------------------------------
251
252   -- This procedure is called every time a block must be decrypted.
253   -- Also the Offset, Checksum and the number of decrypted blocks
254   -- will be updated. The decrypted block will be first masked
255   -- and then written.
256   procedure Aux_Dec (This     :  in     AE_OCB;
257                      Offset   :  in out Block;
258                      Checksum :  in out Block;
259                      Count    :  in out Positive;
260                      Input    :  in     Block;
261                      Output   :  in out Block) is
262   begin
263
264      Offset := Offset xor This.L_Array(Number_Of_Trailing_Zeros(Count));
265      BC.Decrypt(Input xor Offset, Output);
266      Output := Output xor Offset;
267
268      Checksum := Checksum xor Output;
269      Count := Count + 1;
270
271   end Aux_Dec;
272
273   -----------------------------------------------------------------
274
275   -- This procedure decrypt and write each Ciphertext block. It won't
276   -- be called, if the calculated Tag isn't the same as the specified.
277   procedure Write_Decrypted_Plaintext(This                  : in AE_OCB;
278                                       Read_Ciphertext_Again : in Callback_Reader;
279                                       Write_Plaintext       : in Callback_Writer;
280                                       Dec_Bool              : in Boolean;
281                                       Last_P_Block          : in Bytes;
282                                       Last_B_Bytelen        : in Natural) is
283
284      Bytes_Read: Natural;
285      Blockcount: Positive := 1;
286      Offset: Block := This.Offset;
287      Checksum: Block := Zero_Block;
288      Plaintext: Block;
289
290      First_Block: Bytes := Zero_Bytes;
291      Second_Block: Bytes := Zero_Bytes;
292      Third_Block: Bytes := Zero_Bytes;
293   begin
294      Read_Ciphertext_Again(First_Block, Bytes_Read);
295      if Bytes_Read = 0 then
296         raise Constraint_Error with "Invalid Ciphertext";
297      elsif
298        Bytes_Read < Bytes_Per_Block then
299         null;
300      else
301         Read_Ciphertext_Again(Second_Block, Bytes_Read);
302
303         -- If Bytes_Read = 0, only Last_P_Block must be written
304         -- If (Bytes_Per_Block > Bytes_Read > 0) and Dec_Bool = True then
305         -- First_Block will be decrypt, else only Last_P_Block will be written
306         if Bytes_Read = Bytes_Per_Block then
307            loop
308               Read_Ciphertext_Again(Third_Block, Bytes_Read);
309
310               if Bytes_Read = Bytes_Per_Block then
311                  Aux_Dec(This     => This,
312                          Offset   => Offset,
313                          Checksum => Checksum,
314                          Count    => Blockcount,
315                          Input    => To_Block_Type(First_Block),
316                          Output   => Plaintext);
317                  Write_Plaintext(To_Bytes(Plaintext));
318                  First_Block := Second_Block;
319                  Second_Block := Third_Block;
320               elsif Bytes_Read = 0 then
321                  Bytes_Read := Bytes_Per_Block;
322                  exit;
323               else
324                  Aux_Dec(This     => This,
325                          Offset   => Offset,
326                          Checksum => Checksum,
327                          Count    => Blockcount,
328                          Input    => To_Block_Type(First_Block),
329                          Output   => Plaintext);
330                  Write_Plaintext(To_Bytes(Plaintext));
331
332                  First_Block := Second_Block;
333                  Second_Block := Third_Block;
334                  exit;
335               end if;
336            end loop;
337         end if;
338      end if;
339
340      if Dec_Bool then
341         Aux_Dec(This     => This,
342                 Offset   => Offset,
343                 Checksum => Checksum,
344                 Count    => Blockcount,
345                 Input    => To_Block_Type(First_Block),
346                 Output   => Plaintext);
347         Write_Plaintext(To_Bytes(Plaintext));
348      end if;
349
350      -- write last Plaintext bytes
351      if Last_B_Bytelen > 0 then
352         Write_Plaintext(Last_P_Block(Last_P_Block'First..Last_B_Bytelen-1));
353      end if;
354   end Write_Decrypted_Plaintext;
355
356   -----------------------------------------------------------------
357   ----
358   ---- overriding functions and procedures
359   ----
360   -----------------------------------------------------------------
361
362   procedure Init_Encrypt(This   : out    AE_OCB;
363                          Key    : in     Key_Type;
364                          Nonce  : in out N.Nonce'Class) is
365   begin
366      BC.Prepare_Key(Key);
367      This.Nonce_Value := Nonce.Update;
368      This.Taglen := Bytes_Per_Block;
369      Generate_L(This.L_Array);
370      BC.Encrypt(This.Nonce_Value xor This.L_Array(0), This.Offset);
371   end Init_Encrypt;
372
373   -----------------------------------------------------------------
374
375   procedure Init_Decrypt(This        : out AE_OCB;
376                          Key         : in  Key_Type;
377                          Nonce_Value : in  Block) is
378   begin
379      BC.Prepare_Key(Key);
380      This.Nonce_Value := Nonce_Value;
381      This.Taglen := Bytes_Per_Block;
382      Generate_L(This.L_Array);
383      BC.Encrypt(This.Nonce_Value xor This.L_Array(0), This.Offset);
384   end Init_Decrypt;
385
386   -----------------------------------------------------------------
387
388   procedure Encrypt(This             : in out AE_OCB;
389                     Read_Plaintext   : in     Callback_Reader;
390                     Write_Ciphertext : in     Callback_Writer) is
391
392      Bytes_Read: Natural;
393      Ciphertext : Block;
394      Offset: Block := This.Offset;
395      Blockcount: Positive := 1;
396      Checksum: Block := Zero_Block;
397      X: Block;
398
399      Last_C_Block: Bytes := Zero_Bytes;     -- last Ciphertext block in bytes
400      Last_P_Block: Bytes(Zero_Bytes'Range); -- last Plaintext block in bytes
401      Last_B_Bitlen: Block := Zero_Block;    -- bit-length of the last block represented as Block
402
403      Prev_Block: Bytes := Zero_Bytes;
404      Curr_Block: Bytes := Zero_Bytes;
405   begin
406      Read_Plaintext(Prev_Block, Bytes_Read);
407      if Bytes_Read < Bytes_Per_Block then
408         Last_P_Block(Prev_Block'First..Prev_Block'First+Prev_Block'Length-1)
409           := Prev_Block;
410         Last_B_Bitlen := Convert_Length_To_Block(8 * Bytes_Read);
411      else
412         loop
413            Read_Plaintext(Curr_Block, Bytes_Read);
414
415            if Bytes_Read = Bytes_Per_Block then
416
417               Aux_Enc(This       => This,
418                       Offset     => Offset,
419                       Checksum   => Checksum,
420                       Write      => Write_Ciphertext,
421                       Count      => Blockcount,
422                       Input      => To_Block_Type(Prev_Block),
423                       Output => Ciphertext);
424               Prev_Block := Curr_Block;
425
426            elsif Bytes_Read = 0 then
427               Last_P_Block := Prev_Block;
428               -- Assigning is important for later use:
429               Bytes_Read := Bytes_Per_Block;
430               Last_B_Bitlen := Convert_Length_To_Block(8 * Bytes_Read);
431               exit;
432            else
433               Aux_Enc(This       => This,
434                       Offset     => Offset,
435                       Checksum   => Checksum,
436                       Write      => Write_Ciphertext,
437                       Count      => Blockcount,
438                       Input      => To_Block_Type(Prev_Block),
439                       Output => Ciphertext);
440               Last_P_Block := Curr_Block;
441               Last_B_Bitlen := Convert_Length_To_Block(8 * Bytes_Read);
442               exit;
443            end if;
444
445         end loop;
446      end if;
447
448      Offset := Offset xor This.L_Array(Number_Of_Trailing_Zeros(Blockcount));
449
450      X := Last_B_Bitlen xor This.L_Array(-1) xor Offset; -- length of C[m] in bits represented as an n-bit block
451      BC.Encrypt(X, Ciphertext); -- Ciphertext = Y[m]
452
453      if Bytes_Read > 0 then
454         declare
455            Y: constant Bytes := To_Bytes(Ciphertext);
456         begin
457            Last_C_Block(0..Bytes_Read-1) := Last_P_Block(0..Bytes_Read-1)
458              xor Y(Y'First..Y'First+Bytes_Read-1);
459         end;
460      end if;
461
462      Checksum := Checksum xor Ciphertext xor To_Block_Type(Last_C_Block);
463      -- calculate the Tag
464      BC.Encrypt(Checksum xor Offset, Ciphertext);
465
466      -- concatenate the last block and Tag (if necessary)
467      declare
468         C: constant Bytes := To_Bytes(Ciphertext);
469      begin
470         if Bytes_Read < Bytes_Per_Block then
471            declare
472               -- |B| = |last message block| + |desired Tag|
473               B: Bytes(0..(Bytes_Read+This.Taglen-1));
474            begin
475               -- concatenate last Ciphertext bytes with the Tag
476               B(B'First..Bytes_Read-1)
477                 := Last_C_Block(Last_C_Block'First..Bytes_Read-1);
478               B(Bytes_Read..B'Last) := C(C'First..C'First+This.Taglen-1);
479               if B'Length > Bytes_Per_Block then
480                  Write_Ciphertext(B(B'First..Bytes_Per_Block-1));
481                  declare
482                     -- This step is only for normalizing the index (starting at 0)
483                     Temp: constant Bytes(0..(B'Length-Bytes_Per_Block)-1)
484                       := B(Bytes_Per_Block..B'Last);
485                  begin
486                     Write_Ciphertext(Temp);
487                  end;
488               else
489                  Write_Ciphertext(B(B'First..B'Last));
490               end if;
491            end;
492         else
493            -- write the last Ciphertext block an the Tag
494            Write_Ciphertext(Last_C_Block);
495            Write_Ciphertext(C(C'First..This.Taglen-1));
496         end if;
497      end;
498
499   end Encrypt;
500
501   -----------------------------------------------------------------
502
503   function Aux_Decrypt(This                   : in AE_OCB;
504                        Read_Ciphertext        : in Callback_Reader;
505                        Read_Ciphertext_Again  : in Callback_Reader;
506                        Write_Plaintext        : in Callback_Writer)
507                        return Boolean is
508
509      Bytes_Read: Natural;
510      Blockcount: Positive := 1;
511      Offset: Block := This.Offset;
512      Checksum: Block := Zero_Block;
513      Plaintext: Block;
514      Tag: Bytes := Zero_Bytes;
515      T: Block;
516      Dec_Bool: Boolean;
517      Verification_Bool: Boolean := False;
518
519      Last_P_Block: Bytes := Zero_Bytes;  -- last Plaintext block in bytes
520      Last_C_Block: Bytes := Zero_Bytes;  -- last Ciphertext block in bytes
521      Last_B_Bitlen: Block := Zero_Block; -- bit-length of the last block represented as Block
522      Last_B_Bytelen: Natural;            -- byte-length of the last block
523
524      First_Block: Bytes := Zero_Bytes;
525      Second_Block: Bytes := Zero_Bytes;
526      Third_Block: Bytes := Zero_Bytes;
527   begin
528      Read_Ciphertext(First_Block, Bytes_Read);
529
530      if Bytes_Read = 0 then
531         -- Tag must be at least 1 byte
532	 raise Constraint_Error with "Invalid Ciphertext";
533      elsif Bytes_Read < Bytes_Per_Block then
534         Extract(This       => This,
535                 A          => First_Block,
536                 Bytes_Read => Bytes_Read,
537                 Bitlen     => Last_B_Bitlen,
538                 Bytelen    => Last_B_Bytelen,
539                 Last_Block => Last_C_Block,
540                 Tag        => Tag,
541                 Two_Blocks => False,
542                 Dec        => Dec_Bool);
543      else
544         Read_Ciphertext(Second_Block, Bytes_Read);
545
546         if Bytes_Read < Bytes_Per_Block then
547            if Bytes_Read = 0 then
548               -- First_Block was the last block and filled up
549               Bytes_Read := Bytes_Per_Block;
550               Extract(This       => This,
551                       A          => First_Block,
552                       Bytes_Read => Bytes_Read,
553                       Bitlen     => Last_B_Bitlen,
554                       Bytelen    => Last_B_Bytelen,
555                       Last_Block => Last_C_Block,
556                       Tag        => Tag,
557                       Two_Blocks => False,
558                       Dec        => Dec_Bool);
559            else
560               Extract(This       => This,
561                       A          => First_Block,
562                       B          => Second_Block,
563                       Bytes_Read => Bytes_Read,
564                       Bitlen     => Last_B_Bitlen,
565                       Bytelen    => Last_B_Bytelen,
566                       Last_Block => Last_C_Block,
567                       Tag        => Tag,
568                       Two_Blocks => True,
569                       Dec        => Dec_Bool);
570            end if;
571         else
572            loop
573               Read_Ciphertext(Third_Block, Bytes_Read);
574
575               if Bytes_Read = Bytes_Per_Block then
576                  Aux_Dec(This     => This,
577                          Offset   => Offset,
578                          Checksum => Checksum,
579                          Count    => Blockcount,
580                          Input    => To_Block_Type(First_Block),
581                          Output   => Plaintext);
582
583                  if Store_Internally then
584                     Masked_Plaintext.Append(First_Block);
585                  end if;
586
587                  First_Block := Second_Block;
588                  Second_Block := Third_Block;
589               elsif Bytes_Read = 0 then
590                  -- Second_Block was a full block
591                  Bytes_Read := Bytes_Per_Block;
592                  Extract(This       => This,
593                          A          => First_Block,
594                          B          => Second_Block,
595                          Bytes_Read => Bytes_Read,
596                          Bitlen     => Last_B_Bitlen,
597                          Bytelen    => Last_B_Bytelen,
598                          Last_Block => Last_C_Block,
599                          Tag        => Tag,
600                          Two_Blocks => True,
601                          Dec        => Dec_Bool);
602                  exit;
603               else
604                  -- decrypt First_Block
605                  Aux_Dec(This     => This,
606                          Offset   => Offset,
607                          Checksum => Checksum,
608                          Count    => Blockcount,
609                          Input    => To_Block_Type(First_Block),
610                          Output   => Plaintext);
611
612                  if Store_Internally then
613                     Masked_Plaintext.Append(First_Block);
614                  end if;
615
616                  -- Assigning is important because, if Dec_Bool = True,
617                  -- First_Block will be used later for decryption.
618                  First_Block := Second_Block;
619                  Second_Block := Third_Block;
620
621                  Extract(This       => This,
622                          A          => First_Block,
623                          B          => Second_Block,
624                          Bytes_Read => Bytes_Read,
625                          Bitlen     => Last_B_Bitlen,
626                          Bytelen    => Last_B_Bytelen,
627                          Last_Block => Last_C_Block,
628                          Tag        => Tag,
629                          Two_Blocks => True,
630                          Dec        => Dec_Bool);
631                  exit;
632               end if;
633            end loop;
634         end if;
635      end if;
636
637      -- If B containts last Ciphertext bytes
638      -- and the Tag, A must be decrypt.
639      if Dec_Bool then
640         Aux_Dec(This     => This,
641                 Offset   => Offset,
642                 Checksum => Checksum,
643                 Count    => Blockcount,
644                 Input    => To_Block_Type(First_Block),
645                 Output   => Plaintext);
646      end if;
647
648      Offset := Offset xor This.L_Array(Number_Of_Trailing_Zeros(Blockcount));
649
650      declare
651         X: Block;
652      begin
653         X := Last_B_Bitlen xor This.L_Array(-1) xor Offset;
654         BC.Encrypt(X, Plaintext);
655      end;
656
657      if Last_B_Bytelen > 0 then -- only false if |Message| = 0
658         declare
659            Y: constant Bytes := To_Bytes(Plaintext);
660         begin
661            Last_P_Block(0..Last_B_Bytelen-1)
662              := Last_C_Block(Last_C_Block'First..Last_B_Bytelen-1)
663              xor Y(Y'First..Y'First+Last_B_Bytelen-1);
664         end;
665      end if;
666
667      Checksum := Checksum xor Plaintext xor To_Block_Type(Last_C_Block);
668      BC.Encrypt(Checksum xor Offset, T);
669
670      declare
671         Calculated_Tag: constant Bytes := To_Bytes(T);
672      begin
673         if Tag(Tag'First..This.Taglen-1)
674           = Calculated_Tag(Calculated_Tag'First..This.Taglen-1) then
675            Verification_Bool := True;
676            Write_Decrypted_Plaintext
677              (This                  => This,
678               Read_Ciphertext_Again => Read_Ciphertext_Again,
679               Write_Plaintext       => Write_Plaintext,
680               Dec_Bool              => Dec_Bool,
681               Last_P_Block          => Last_P_Block,
682               Last_B_Bytelen        => Last_B_Bytelen);
683         end if;
684      end;
685
686      return Verification_Bool;
687
688   end Aux_Decrypt;
689
690   -----------------------------------------------------------------
691
692   function Decrypt_And_Verify
693     (This                   : in out AE_OCB;
694      Read_Ciphertext        : in     Callback_Reader;
695      Read_Ciphertext_Again  : in     Callback_Reader := null;
696      Write_Plaintext        : in     Callback_Writer)
697      return Boolean is
698
699      RCA: constant Callback_Reader := Read_Masked_Plaintext'Access;
700   begin
701      if Read_Ciphertext_Again = null then
702
703         Store_Internally := True;
704
705         return Aux_Decrypt(This                   => This,
706                            Read_Ciphertext        => Read_Ciphertext,
707                            Read_Ciphertext_Again  => RCA,
708                            Write_Plaintext        => Write_Plaintext);
709      else
710         return Aux_Decrypt(This                   => This,
711                            Read_Ciphertext        => Read_Ciphertext,
712                            Read_Ciphertext_Again  => Read_Ciphertext_Again,
713                            Write_Plaintext        => Write_Plaintext);
714      end if;
715
716   end Decrypt_And_Verify;
717
718   -----------------------------------------------------------------
719   ----
720   ---- additional functions and procedures
721   ----
722   -----------------------------------------------------------------
723
724   procedure Init_Encrypt(This   : out    AE_OCB;
725                          Key    : in     Key_Type;
726                          Nonce  : in out N.Nonce'Class;
727                          Taglen : in     Positive) is
728   begin
729      BC.Prepare_Key(Key);
730      This.Nonce_Value := Nonce.Update;
731      This.Taglen := Taglen;
732      Generate_L(This.L_Array);
733      BC.Encrypt(This.Nonce_Value xor This.L_Array(0), This.Offset);
734
735   end Init_Encrypt;
736
737   -----------------------------------------------------------------
738
739   procedure Init_Decrypt(This        : out AE_OCB;
740                          Key         : in  Key_Type;
741                          Nonce_Value : in  Block;
742                          Taglen      : in  Positive) is
743   begin
744      BC.Prepare_Key(Key);
745      This.Nonce_Value := Nonce_Value;
746      This.Taglen := Taglen;
747      Generate_L(This.L_Array);
748      BC.Encrypt(This.Nonce_Value xor This.L_Array(0), This.Offset);
749
750   end Init_Decrypt;
751
752   -----------------------------------------------------------------
753
754end Crypto.Symmetric.AE_OCB;
755