-- Copyright (C) 1984  by Xerox Corporation. All rights reserved. 
-- DESDicentra.mesa, HGM, 12-Jan-84 22:47:54

DIRECTORY
  Environment USING [Byte],
  Inline USING [DBITXOR],
  
  DicentraInputOutput USING [Input, IOAddress, Output, ReadHole, WriteHole],
  DESFace USING [Block, Blocks, Direction, IV, Key, Mode, parityTable],
  MultibusAddresses USING [desByte, desWord];

DESDicentra: MONITOR IMPORTS Inline, DicentraInputOutput EXPORTS DESFace SHARES DESFace =
  BEGIN
  
  <<
  
  Unless you check the status bits, you have to wait "long enough" in several places.
    I can't find these restrictions anyplace in the spec sheet.
    There is a hint of some on pg 11 for the direct control mode.
  
  The ones I know about are:
    6 clocks after any command or set mode.
      Note that the hardware does this automaticaly if you use byte accesses.
    18 clocks (maybe more) for a data block to trickle through the chip.
    6 clocks after writing a block before writing another block.
    6 clocks after reading a block before reading the next block (assuming there is one).
      This code pipelines things by writing the second block before reading the first.
      Except for the 1 block case, that seems to provide the required delay.
    
    If you tweak this code, or the microcode, and it stops working,
      consider inserting some delays.
    
  >>
  
  BadParity: ERROR = CODE;
  NotImplemented: ERROR = CODE;
  
  desChip: DicentraInputOutput.IOAddress = MultibusAddresses.desByte;
  desWord: DicentraInputOutput.IOAddress = MultibusAddresses.desWord;
  
  Register: TYPE = MACHINE DEPENDENT {
    data(0), command(1), mode(3)};
  
  DESMP: PROCEDURE [where: Register, byte: Environment.Byte] = INLINE
    BEGIN
    DicentraInputOutput.Output[byte, desChip+LOOPHOLE[where, CARDINAL]];
    END;
  
  DESWriteBlock: PROCEDURE [p: LONG POINTER TO DESFace.Block] = INLINE
    BEGIN
    DicentraInputOutput.WriteHole[
      from: p,
      to: desWord+LOOPHOLE[Register[data]],
      words: SIZE[DESFace.Block]];
    END;
    
  DESReadBlock: PROCEDURE [p: LONG POINTER TO DESFace.Block] = INLINE
    BEGIN
    DicentraInputOutput.ReadHole[
      to: p,
      from: desWord+LOOPHOLE[Register[data]],
      words: SIZE[DESFace.Block]];
    END;

  ResetTheChip: PROCEDURE =
    BEGIN
    DESMP[command, 00H];
    END;
    
  LoadIV: PROCEDURE [ivP: LONG POINTER TO DESFace.IV, direction: DESFace.Direction] =
    BEGIN
    iv: LONG POINTER TO DESFace.Block = LOOPHOLE[ivP];
    DESMP[command, IF direction = encrypt THEN 85H ELSE 84H];
    DESWriteBlock[iv];
    END;
    
  LoadKey: PROCEDURE [keyP: LONG POINTER TO DESFace.Key, direction: DESFace.Direction] =
    BEGIN
    key: LONG POINTER TO DESFace.Block = LOOPHOLE[keyP];
    FOR i: CARDINAL IN [0..7] DO
      IF keyP[i].p # DESFace.parityTable[keyP[i].b] THEN ERROR BadParity;
      ENDLOOP;
    DESMP[command, IF direction = encrypt THEN 11H ELSE 12H];
    DESWriteBlock[key];
    END;
    
  SetMode: PROCEDURE [mode: DESFace.Mode, direction: DESFace.Direction] =
    BEGIN
    byte: Environment.Byte;
    SELECT direction FROM
      encrypt => byte ← 18H;
      decrypt => byte ← 08H;
      ENDCASE => ERROR;
    SELECT mode FROM
      ecb => NULL;
      cbc => byte ← byte + 2;
      cbcCheck => byte ← byte + 2;
      ENDCASE => ERROR;
    DESMP[mode, byte];
    END;
    
  Crunch: PROCEDURE [from, to: DESFace.Blocks, nBlks: CARDINAL] =
    BEGIN
    DESMP[command, 0C0H];  -- Start
    IF nBlks = 0 THEN RETURN;
    DicentraInputOutput.WriteHole[
      from: @from[0],
      to: desWord+LOOPHOLE[Register[data]],
      words: SIZE[DESFace.Block]];
    from ← from + SIZE[DESFace.Block];
    nBlks ← nBlks - 1;
    IF nBlks = 0 THEN
      BEGIN  -- Read Status so hardware provides the delay
      status: CARDINAL = 1;
      [] ← DicentraInputOutput.Input[desChip+status];
      [] ← DicentraInputOutput.Input[desChip+status];
      [] ← DicentraInputOutput.Input[desChip+status];
      END;
    UNTIL nBlks < 4 DO  -- Unroll the loop a bit
      DicentraInputOutput.WriteHole[
        from: @from[0],
        to: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      DicentraInputOutput.ReadHole[
        to: @to[0],
        from: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      DicentraInputOutput.WriteHole[
        from: @from[1],
        to: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      DicentraInputOutput.ReadHole[
        to: @to[1],
        from: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      DicentraInputOutput.WriteHole[
        from: @from[2],
        to: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      DicentraInputOutput.ReadHole[
        to: @to[2],
        from: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      DicentraInputOutput.WriteHole[
        from: @from[3],
        to: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      DicentraInputOutput.ReadHole[
        to: @to[3],
        from: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      from ← from + 4*SIZE[DESFace.Block];
      to ← to + 4*SIZE[DESFace.Block];
      nBlks ← nBlks - 4;
      ENDLOOP;
    UNTIL nBlks = 0 DO
      DicentraInputOutput.WriteHole[
        from: @from[0],
        to: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      DicentraInputOutput.ReadHole[
        to: @to[0],
        from: desWord+LOOPHOLE[Register[data]],
        words: SIZE[DESFace.Block]];
      from ← from + SIZE[DESFace.Block];
      to ← to + SIZE[DESFace.Block];
      nBlks ← nBlks - 1;
      ENDLOOP;
    DicentraInputOutput.ReadHole[
      to: @to[0],
      from: desWord+LOOPHOLE[Register[data]],
      words: SIZE[DESFace.Block]];
    END;
    
  CryptData: PUBLIC ENTRY PROCEDURE [
    keyP: POINTER TO DESFace.Key, nBlks: CARDINAL, from, to: DESFace.Blocks,
    direction: DESFace.Direction, mode: DESFace.Mode,
    seedP: LONG POINTER TO DESFace.IV ← NIL] =
    BEGIN ENABLE UNWIND => NULL;
    
    IF mode = checksum THEN ERROR NotImplemented;

    IF mode = cbcCheck AND direction = encrypt AND nBlks > 0 THEN
      BEGIN
      last: LONG POINTER TO DESFace.Block = @from[nBlks - 1];
      FOR blk: CARDINAL IN [0..nBlks - 1) DO
        XOR64[last, @from[blk], last]; ENDLOOP;
      END;

    ResetTheChip[];
    
    SetMode[mode, direction];
    
    LoadKey[keyP, direction];
    
    IF mode = cbc OR mode = cbcCheck THEN LoadIV[seedP, direction];
    
    Crunch[from, to, nBlks];

    IF mode = cbcCheck AND direction = decrypt AND nBlks > 0 THEN
      BEGIN
      last: LONG POINTER TO DESFace.Block = @to[nBlks - 1];
      FOR blk: CARDINAL IN [0..nBlks - 1) DO
        XOR64[last, @to[blk], last]; ENDLOOP;
      END

    END;
    
    
  Words4: TYPE = MACHINE DEPENDENT RECORD [a, b: LONG CARDINAL];

  XOR64: PROCEDURE [a, b, out: LONG POINTER] = INLINE
    BEGIN OPEN
      aLP: LOOPHOLE[a, LONG POINTER TO Words4],
      bLP: LOOPHOLE[b, LONG POINTER TO Words4],
      outP: LOOPHOLE[out, LONG POINTER TO Words4];

    outP.a ← Inline.DBITXOR[aLP.a, bLP.a];
    outP.b ← Inline.DBITXOR[aLP.b, bLP.b];

    END;




  END.