Dynamic Substitution/Transposition Example Sources

Terry Ritter terry at inebriae.UUCP
Tue Nov 28 18:39:49 AEST 1989


#! /bin/sh
# This is a shell archive, meaning:
# 1. Remove everything above the #! /bin/sh line.
# 2. Save the resulting text in a file.
# 3. Execute the file with /bin/sh (not csh) to create:
#	cryp/dyndoc.txt
#	cryp/dynsub.pas
#	cryp/dyntran.pas
#	cryp/readme.txt
# This archive created: Tue Nov 28 01:18:04 1989
export PATH; PATH=/bin:/usr/bin:$PATH
if test -f 'cryp/dyndoc.txt'
then
	echo shar: "will not over-write existing file 'cryp/dyndoc.txt'"
else
cat << \SHAR_EOF > 'cryp/dyndoc.txt'
 
Programs DYNSUB and DYNTRAN                     November 5, 1989
 
     Terry Ritter         (512) 892-0494
     Blue Jean Computer Engineering
     2609 Choctaw Trail
     Austin, TX 78745
 
 
     These programs are intended to explain the algorithms for two
"cryptographic combiner" mechanisms which I seem to have invented.  The
programs also provide the basis for assessing the effectiveness of these
mechanisms.  Each of the two programs combines pseudo-random values with
data from standard input, and sends the result to standard output.  Two
command-line parameters allow selection of "decipher mode" (/d) and
initialization of the RNG with a selected key value (/k).  
 
     These combiners tend to obstruct a "known-plaintext" attack, since they
do not easily disclose the pseudo-random sequence, even if the original
plaintext data is available with the corresponding ciphertext.  Since the
pseudo-random sequence is generally produced algorithmically, if it becomes
available for analysis, it might (potentially) be fully analyzed and
reproduced, which would naturally penetrate the system. 
 
     Both of the combiners seem to produce a pseudo-random output if either
one of their inputs is random-like (even if the other input is a CONSTANT
value).  This may be a requirement for a secure cryptographic combiner, and
is comparable to the statistical performance of exclusive-OR.  I call the
two schemes "The Dynamic Substitution Combiner" and "The Dynamic
Transposition Combiner," for reasons which will soon become apparent.  
 
 
DYNAMIC SUBSTITUTION
 
     First, we map characters or bytes through a substitution table; this is
Simple Substitution.  Then, after each byte is mapped, we CHANGE the
contents of the table.  Thus, the substitution is "dynamic" in the sense
that the substitution mapping changes as time goes on.  
 
     For example, as in the program DYNSUB, we might exchange the just-used
table element with some table element selected at random.  So whenever a
substitution element is used, that substitution is (probably) changed, and
the more often it is used, the more often it is changed.  It will be seen
that this mechanism AUTOMATICALLY compensates for any uneven frequency
distribution in the source text.  Since an uneven distribution is the most
common way to break a substitution cipher, frustrating this approach seems
to be a significant result.  
 
     In addition, the pseudo-random sequence operates only in the background,
to re-arrange the table.  In this way, the substitution table continues to
change, and the pseudo-random sequence is hidden.  Of course, in
cryptography, "hidden" is a relative term. 
 
     For deciphering, an inverse table is maintained and permuted
appropriately; to do this efficiently, a non-inverse table is also
maintained and permuted.  Different symbol alphabets and multi-table
polyalphabetic versions are some obvious extensions of the basic mechanism. 
 
 
DYNAMIC TRANSPOSITION
 
     First, we fill a block with data, and then shuffle the block; this is
a form of block transposition (permutation).  In particular, as in the
program DYNTRAN, we step through the block element-by-element, and exchange
the current element with some element at random; in this way, the pseudo-
random sequence selects a particular block permutation.  The mechanism is
"dynamic" in the sense that no two blocks need be permuted similarly; the
block permutation thus changes through time.  We also note that such a
permutation is reversible, provided that the pseudo-random sequence can be
made available in reverse.  
 
     There are some tricks:  First, we shuffle BITS, not bytes; this takes
longer, but works much better.  (The bits of any particular byte may end
up anywhere in the block.)  Second, we arrange to "bit-balance" each block,
so that EVERY block contains EXACTLY half 1-bits and half 0-bits.  This is
done by counting the data bits as the block is being filled, and adding
appropriate bit-balance data to fill out the block.  The bit-balancing 
gives us a way to GUARANTEE a powerful encipherment, since the strength of
a block-permutation is dependent on the frequency distribution of the
particular data being enciphered.  (Permuting a block filled with
occurrences of exactly one value does little good.)  The bit-compensation
data will be identified and removed as part of deciphering.  And we can
reverse the pseudo-random sequence (for deciphering) by buffering the
desired number of values, and using them from the buffer in reverse.  
 
     Whenever we deal with data in whole blocks only, the last block may be
only partially filled with data, and thus may need to be "padded" to fill
it out.  But we can arrange the padding so that it is removed with the same
mechanism used to remove the bit-compensation.  For deciphering, we do the
same bit-exchanges as were done in the enciphering shuffle, only in reverse
order, and this puts everything back where it was.  
 
     Since many different random sequences can produce the same block
permutation, the pseudo-random sequence seems well hidden.  Since there can
be no way to know which bits belong together, the data itself also seems
well hidden.  And the bit-balancing would seem to prevent even a bit-level
frequency distribution analysis.  
 
     Allowing different size blocks, stepping through a block in a non-
sequential order, and continuing beyond a single pass through a block are
other obvious extensions of the basic mechanism.  Since encryption overhead
is linear with the amount of data, very large data "blocks" can be
accommodated efficiently, and they need not have an even binary length. 
The combiner can also permute a block initialized as a counting sequence,
and end up with an explicit definition of the resulting permutation (each
element will bear the value of its previous position).  This definition can
then be used either for combining or extracting.  
 
 
PROGRAM EXAMPLES
 
     An example software implementation is given for each type of combiner. 
The examples are given in Turbo Pascal 5.5 source code, since this is what
I generally use.  Obviously, the combiners could be implemented in hardware
instead of software, and would make especially nice integrated circuits. 
The example programs are cut down as much as possible, to show the logic
clearly, so they are NOT intended to be cryptographic systems.  For
example, the programs use the Turbo Pascal RNG, which may be fine for
statistics, but is not a good idea for serious cryptographic work.  Also,
neither program implements a "message key" or any other approach to prevent
re-use of a particular pseudo-random sequence.  Various other features
necessary for serious security are also omitted.  As they stand, however,
they are probably more secure than some common approaches.  
 
     The example programs DYNSUB and DYNTRAN function under DOS, and take
input from StdIn and send output to StdOut; in general, these would be
files.  Note that the user must specify these files on the command line as
part of the invocation (e.g., "<inputfile >outputfile").  Each program has
two optional parameters (which may each be placed anywhere on the command
line): "/d", which means "decipher mode" (as opposed to the default
"encipher mode"), and "/k", which introduces a key value.  The key value
is a 9.3 decimal digit positive or negative integer (-2,147,483,648 through
2,147,483,647) which is converted to a 32-bit binary value to initialize
the Turbo RNG.  
 
 
     For example:  
 
     "dynsub <plain.txt >cipher.txt /k = -1234567890" 
 
enciphers the file "plain.txt" into the file "cipher.txt"; then 
 
     "dynsub /d <cipher.txt >plain2.txt /k = -1234567890" 
 
deciphers it.  The plaintext files may be of any length, and may contain
any byte values.  Executable files may be enciphered, as may archive
(library) files.  Program DYNTRAN operates in a similar way.  
 
 
FEEDBACK
 
     Naturally, I would be interested in comments relating to these
mechanisms; please use U.S. "snail mail."  
 
SHAR_EOF
fi
if test -f 'cryp/dynsub.pas'
then
	echo shar: "will not over-write existing file 'cryp/dynsub.pas'"
else
cat << \SHAR_EOF > 'cryp/dynsub.pas'
 
      { dynsub.pas, 89/11/5/tfr (from 11/4, 10/25, 9/15, 8/29) }
      { dynamic substitution cipher DEMONSTRATION }
      {    uses the Turbo Pascal RNG, which is insecure }
      { enciphers StdIn to StdOut; use command line "/d" to decipher }
      { use command line "/k" to enter key, a 32-bit 2's comp value }
      {    for example, "/k = -1234567890" }
      { (c) Copyright 1989, T. F. Ritter; All Rights Reserved }
 
 
 
 
      PROGRAM dynsub;
 
 
      {$A+}   { Word Alignment ON }
      {$B-}   { Full Boolean Evaluation OFF }
      {$D+}   { Debug Information ON }
      {$F-}   { Far Calls OFF }
      {$I-}   { I/O-Checking OFF }
      {$L+}   { Local Symbols ON }
      {$N-}   { Numeric Co-Processor OFF }
      {$O-}   { Overlay Code OFF }
      {$V-}   { VAR-String Checking OFF }
      {$R+}   { Range-Checking ON }
      {$S+}   { Stack-Checking ON }
 
 
 
      TYPE
         Str127 = STRING[ 127 ];
 
      VAR
         CmdLinP: ^Str127;
 
 
 
      PROCEDURE lcST( VAR s: STRING );
         VAR
            i: BYTE;
         BEGIN
         FOR i := 1 TO Length(s) DO
            CASE s[i] OF
            'A'..'Z': Inc( s[i], ORD('a') - ORD('A') );
            END; {case}
         END; {lcST}
 
 
 
      PROCEDURE ExchangeChars( VAR x, y: CHAR );
         VAR
            t: CHAR;
         BEGIN
         t := x;  x := y;  y := t;
         END; {ExchangeChars}
 
 
 
      VAR
         ch: CHAR;
         f, finv: ARRAY[ CHAR ] of CHAR;
 
 
 
      PROCEDURE DynSubInit;
         BEGIN
         FOR ch := #0 TO #255 DO  f[ ch ] := ch;
         FOR ch := #0 TO #255 DO
            ExchangeChars( f[ ch ], f[ CHAR(Random(256)) ] );
         END; {DynSubInit}
 
 
      FUNCTION DynSubF( xi: CHAR ): CHAR;
         BEGIN
         DynSubF := f[xi];
         ExchangeChars( f[xi], f[ CHAR(Random(256)) ] );
         END; {DynSubF}
 
 
      PROCEDURE InvDynSubInit;
         BEGIN
         DynSubInit;
         FOR ch := #0 TO #255 DO  finv[ f[ ch ] ] := ch;
         END; {InvDynSubInit}
 
 
      FUNCTION InvDynSubF( yi: CHAR ): CHAR;
         VAR
            j, xi, yj: CHAR;
         BEGIN
         xi := finv[yi];
         j := CHAR( Random(256) );
         yj := f[j];
         ExchangeChars( finv[yi], finv[yj] );
         ExchangeChars( f[xi], f[j] );
         InvDynSubF := xi;
         END; {InvDynSubF}
 
 
 
 
      VAR
         fromfi, tofi: FILE;
         buf: ARRAY[ 0..511 ] of CHAR;
 
 
      PROCEDURE encipher;
         VAR
            i, got, did: WORD;
         BEGIN
         DynSubInit;
            REPEAT
            BlockRead( fromfi, buf, SizeOf(buf), got );
            IF (got = 0) THEN  Exit;
            FOR i := 0 TO PRED(got) DO
               buf[i] := DynSubF( buf[i] );
            BlockWrite( tofi, buf, got, did );
            UNTIL (did <> got);
         END; {encipher}
 
 
      PROCEDURE decipher;
         VAR
            i, got, did: WORD;
         BEGIN
         InvDynSubInit;
            REPEAT
            BlockRead( fromfi, buf, SizeOf(buf), got );
            IF (got = 0) THEN  Exit;
            FOR i := 0 TO PRED(got) DO
               buf[i] := InvDynSubF( buf[i] );
            BlockWrite( tofi, buf, got, did );
            UNTIL (did <> got);
         END; {decipher}
 
 
      PROCEDURE GetKey;
         VAR
            i, j, len: BYTE;
            res: INTEGER;
         BEGIN
         RandSeed := -1;  { default 32-bit key }
         i := Pos( '/k', CmdLinP^ );
         IF (i <> 0) THEN
            BEGIN
            len := Length( CmdLinP^ );
            WHILE (i < len) AND NOT (CmdLinP^[i] IN ['0'..'9','-']) DO  Inc(i);
            j := i;
            WHILE (j <= len) AND (CmdLinP^[j] IN ['0'..'9', '-']) DO  Inc(j);
            Val( Copy( CmdLinP^, i, j - i ), RandSeed, res );
            END;
         END; {GetKey}
 
 
      PROCEDURE CipherFile;
         BEGIN
         ASSIGN( fromfi, '' );  { StdIn }
         RESET( fromfi, 1 );
         IF (IOresult = 0) THEN
            BEGIN
            ASSIGN( tofi, '' );  { StdOut }
            REWRITE( tofi, 1 );
            IF (IOresult = 0) THEN
               BEGIN
               IF (Pos('/d',CmdLinP^) <> 0) THEN
                  decipher
               ELSE
                  encipher;
               CLOSE( tofi );
               END;
            CLOSE( fromfi );
            END;
         END; {CipherFile}
 
 
      BEGIN
      CmdLinP := Ptr( PrefixSeg, $80 );
      lcST( CmdLinP^ );
      GetKey;
      CipherFile;
      END.
 
 
      { end file dynsub.pas }

SHAR_EOF
fi
if test -f 'cryp/dyntran.pas'
then
	echo shar: "will not over-write existing file 'cryp/dyntran.pas'"
else
cat << \SHAR_EOF > 'cryp/dyntran.pas'
 
      { dyntran.pas, 89/11/5/tfr (from 11/4, 10/25, 9/15,14, 8/29) }
      { dynamic transposition cipher DEMONSTRATION }
      {    uses the Turbo Pascal RNG, which is insecure }
      { enciphers StdIn to StdOut; use command line "/d" to decipher }
      { use command line "/k" to enter key, a 2's comp 32-bit value }
      {    for example, "/k = -1234567890" }
      { (c) Copyright 1989, T. F. Ritter; All Rights Reserved }
 
 
 
 
      PROGRAM dyntran;
 
 
      {$A+}   { Word Alignment ON }
      {$B-}   { Full Boolean Evaluation OFF }
      {$D+}   { Debug Information ON }
      {$F-}   { Far Calls OFF }
      {$I-}   { I/O-Checking OFF }
      {$L+}   { Local Symbols ON }
      {$N-}   { Numeric Co-Processor OFF }
      {$O-}   { Overlay Code OFF }
      {$V-}   { VAR-String Checking OFF }
      {$R+}   { Range-Checking ON }
      {$S+}   { Stack-Checking ON }
 
 
 
      TYPE
         Str127 = STRING[ 127 ];
 
      VAR
         CmdLinP: ^Str127;
 
 
 
      PROCEDURE lcST( VAR s: STRING );
         VAR
            i: BYTE;
         BEGIN
         FOR i := 1 TO Length(s) DO
            CASE s[i] OF
            'A'..'Z': Inc( s[i], ORD('a') - ORD('A') );
            END; {case}
         END; {lcST}
 
 
 
      TYPE
         ByteArray = ARRAY[ 0..65520 ] of BYTE;
 
 
 
      PROCEDURE XchgMapBits( VAR bitmap; lastBYTE, bitno1, bitno2: WORD );
         VAR
            babm: ByteArray ABSOLUTE bitmap;
            byteno1, byteno2: WORD;
            datby1, datby2, mask1, mask2: BYTE;
         BEGIN
         byteno1 := bitno1 Shr 3;
         byteno2 := bitno2 Shr 3;
         datby1 := babm[ byteno1 ];
         datby2 := babm[ byteno2 ];
         mask1 := 1 Shl (bitno1 AND 7);
         mask2 := 1 Shl (bitno2 AND 7);
         IF ((datby1 AND mask1) <> 0) <>
            ((datby2 AND mask2) <> 0) THEN
            BEGIN
            datby1 := datby1 XOR mask1;
            datby2 := datby2 XOR mask2;
            IF (byteno1 <> byteno2) THEN
               babm[ byteno1 ] := datby1
            ELSE
               datby2 := datby1 XOR mask2;
            babm[ byteno2 ] := datby2;
            END;
         END; {XchgMapBits}
 
 
 
      FUNCTION ByteBitCount( by: BYTE ): BYTE;
         VAR
            lby: BYTE;
         BEGIN
         lby := 0;
         WHILE (by <> 0) DO
            BEGIN
            IF ODD(by) THEN  Inc( lby );
            by := by Shr 1;
            END;
         ByteBitCount := lby;
         END; {ByteBitCount}
 
 
 
      CONST
         bufsize = 512;
         bufbits = bufsize Shl 3;
 
      VAR
         frombuf, tobuf: ARRAY[ 0..PRED(bufsize) ] of CHAR;
         randbuf: ARRAY[ 0..PRED(bufbits) ] of WORD;
         fromind, toind: WORD;
 
 
 
      PROCEDURE DynamicTranspose;
         VAR
            i, rand: WORD;
         BEGIN
 
         { shuffle the buffer, bit by bit }
         FOR i := 0 TO PRED(bufbits) DO
            BEGIN
            rand := Random( bufbits );
            XchgMapBits( tobuf, PRED(bufsize), i, rand );
            END;
 
         END; {DynamicTranspose}
 
 
 
      PROCEDURE InvDynamicTranspose;
         VAR
            i: WORD;
         BEGIN
 
         { collect a random value for each bit in the buffer }
         FOR i := 0 TO PRED(bufbits) DO
            randbuf[i] := Random( bufbits );
 
         { unshuffle the buffer, bit by bit }
         FOR i := PRED(bufbits) DOWNTO 0 DO
            XchgMapBits( frombuf, PRED(bufsize), i, randbuf[i] );
 
         END; {InvDynamicTranspose}
 
 
 
      VAR
         fromfi, tofi: FILE;
         totones, totzeros: WORD;
         bittarget, bittest: WORD;
 
 
 
      PROCEDURE DynTranInit;
         VAR
            i: BYTE;
         BEGIN
 
         toind := 0;
         totones := 0;  totzeros := 0;
 
         { the number of 1's and 0's in each block }
         {    half of each => bytes x 4 }
         bittarget := bufsize Shl 2;
 
         bittest := bittarget - 8;
         END; {DynTranInit}
 
 
 
      PROCEDURE DynTranPutTo( ch: CHAR );
         { fill block char-by-char, append bit-balancing, }
         {    then transpose the block and send it }
         VAR
            ones, balancebytes: WORD;
         BEGIN
 
         { we know how many bits are required to balance the block }
         {    so process data until one type is within 1..8 bits of that }
 
         { we finish that bit type with a single selected byte }
         {    and the rest of the block belongs to the other bit type }
 
         tobuf[ toind ] := ch;
         Inc( toind );
 
         ones := ByteBitCount( BYTE(ch) );
         Inc( totones, ones );
         Inc( totzeros, 8 - ones );
 
         IF (totones >= bittest) OR (totzeros >= bittest) THEN
            { we need 1..8 more bits of the most-common type }
            {    AND have AT LEAST two bytes left }
            BEGIN
            IF (totones >= bittest) THEN
               BEGIN
               ch := CHAR( Lo( $ff00 Shr (bittarget - totones) ) );
               tobuf[ toind ] := ch;
               ch := #0;
               END
            ELSE
               BEGIN
               ch := CHAR( $ff Shr (bittarget - totzeros) );
               tobuf[ toind ] := ch;
               ch := #$ff;
               END;
            Inc( toind );
 
            { bit-balancing by byte }
            balancebytes := bufsize - toind;
            FillChar( tobuf[ toind ], balancebytes, ch );
            Inc( toind, balancebytes );
 
            { encipher and store }
            DynamicTranspose;
            BlockWrite( tofi, tobuf, bufsize );
 
            totones := 0;  totzeros := 0;
            toind := 0;
            END;
         END; {DynTranPutTo}
 
 
 
      PROCEDURE DynTranFlushTo;
         { finish the last block: append bit-balancing, }
         {    append padding, transpose the block and send it }
         VAR
            ch: CHAR;
            excessbits, balancebytes, padbytes: WORD;
            lastexcess: BYTE;
         BEGIN
 
         { since DynTranPutTo did not complete the block, }
         {   we KNOW there are MORE THAN two bytes left }
 
         { achieve bit-balance ASAP }
         {   first achieve balance mod 8 in one byte }
         {   then use full bytes to finish off balance }
         {   then use balanced bytes to finish off block }
 
         { bit balance mod 8 is achieved with only 4 selections: }
         {   1,2,3,4; e.g., 1 high (7 low), 2 high (6 low), etc. }
         {   this gives us balancing adjustments of: -6, -4, -2, 0 }
 
         IF (totones >= totzeros) THEN
            BEGIN
 
            excessbits := totones - totzeros;   { current bit unbalance }
               { note that excessbits is always even }
 
            lastexcess := 8 - (excessbits AND 7);   { 1-bits to balance mod 8 }
               { but the balance byte will contain 0's as well as 1's }
               { excessbits AND 7 = excessbits mod 8 = 0,2,4,6 (even) }
               { lastexcess = 8,6,4,2 => 4,3,2,1 one-bits }
 
               { e.g., excessbits (ones, here) = 2 => lastexcess = 6 }
               {   => 3 ones and 5 zeros, a net of 2 balancing zeros }
 
            ch := CHAR( Lo( $ff00 Shr (lastexcess Shr 1) ) );  { 4..1 ones }
            tobuf[ toind ] := ch;   { balance byte }
 
            ch := #0;  { rest will be 0's }
            END
         ELSE
            BEGIN
 
            excessbits := totzeros - totones;
            lastexcess := 8 - (excessbits AND 7);
 
            ch := CHAR( $ff Shr (lastexcess Shr 1) );
            tobuf[ toind ] := ch;
 
            ch := #$ff;  { rest will be 1's }
            END;
         Inc( toind );
 
         { the unbalance here is 0 mod 8 }
 
         { bit-balancing by byte (may have none) }
         {   unbalance div 8 = unbalance Shr 3 = bytes to balance }
         balancebytes := (excessbits + lastexcess - 8) Shr 3;
         FillChar( tobuf[ toind ], balancebytes, ch );
         Inc( toind, balancebytes );
 
         { bit-balanced padding bytes (may have none) }
         padbytes := bufsize - toind;
         FillChar( tobuf[ toind ], padbytes, 'Z' );
         Inc( toind, padbytes);
 
         { encipher and store }
         DynamicTranspose;
         BlockWrite( tofi, tobuf, bufsize );
 
         END; {DynTranFlushTo}
 
 
 
      PROCEDURE InvDynTranInit;
         BEGIN
         END; {InvDynTranInit}
 
 
      PROCEDURE InvDynTranSend;
         { deciphering:  this routine removes BOTH the }
         {   bit-compensation data AND last block padding }
         VAR
            i, j: WORD;
            ch: CHAR;
         BEGIN
 
         InvDynamicTranspose;
 
         i := bufsize;
 
         { skip padding, if any }
            REPEAT
            Dec(i);
            ch := frombuf[i];
            UNTIL (ch <> 'Z');
 
         { skip bit-compensation }
         { delete back through the first non-  all-0's or all-1's byte }
            CASE ch OF
            #0:   REPEAT  Dec(i)  UNTIL  (frombuf[i] <> #0);
            #$ff: REPEAT  Dec(i)  UNTIL  (frombuf[i] <> #$ff);
            END;
 
         { the rest is non-bit-compensation, non-padding: data }
         BlockWrite( tofi, frombuf, i );
 
         END; {InvDynTranSend}
 
 
 
      PROCEDURE encipher;
         VAR
            i, got: WORD;
         BEGIN
         DynTranInit;
            REPEAT
            BlockRead( fromfi, frombuf, bufsize, got );
            IF (got > 0) THEN
               FOR i := 0 TO PRED(got) DO
                  DynTranPutTo( frombuf[i] );
            UNTIL (got <> bufsize);
         IF (toind > 0) THEN  DynTranFlushTo;
         END; {encipher}
 
 
      PROCEDURE decipher;
         VAR
            got: WORD;
         BEGIN
         InvDynTranInit;
            REPEAT
            BlockRead( fromfi, frombuf, bufsize, got );
            IF (got > 0) THEN
               InvDynTranSend;
            UNTIL (got = 0);
         END; {decipher}
 
 
      PROCEDURE GetKey;
         VAR
            i, j, len: BYTE;
            res: INTEGER;
         BEGIN
         RandSeed := -1;  { default 32-bit key }
         i := Pos( '/k', CmdLinP^ );
         IF (i <> 0) THEN
            BEGIN
            len := Length( CmdLinP^ );
            WHILE (i < len) AND NOT (CmdLinP^[i] IN ['0'..'9','-']) DO  Inc(i);
            j := i;
            WHILE (j <= len) AND (CmdLinP^[j] IN ['0'..'9', '-']) DO  Inc(j);
            Val( Copy( CmdLinP^, i, j - i ), RandSeed, res );
            END;
         END; {GetKey}
 
 
      PROCEDURE CipherFile;
         BEGIN
         ASSIGN( fromfi, '' );  { StdIn }
         RESET( fromfi, 1 );
         IF (IOresult = 0) THEN
            BEGIN
            ASSIGN( tofi, '' );  { StdOut }
            REWRITE( tofi, 1 );
            IF (IOresult = 0) THEN
               BEGIN
               IF (Pos('/d',CmdLinP^) <> 0) THEN
                  decipher
               ELSE
                  encipher;
               CLOSE( tofi );
               END;
            CLOSE( fromfi );
            END;
         END; {CipherFile}
 
 
      BEGIN
      CmdLinP := Ptr( PrefixSeg, $80 );
      lcST( CmdLinP^ );
      GetKey;
      CipherFile;
      END.
 
 
      { end file dyntran.pas }

SHAR_EOF
fi
if test -f 'cryp/readme.txt'
then
	echo shar: "will not over-write existing file 'cryp/readme.txt'"
else
cat << \SHAR_EOF > 'cryp/readme.txt'
 
Two New Cryptographic Mechanisms                 November 5, 1989
 
     Terry Ritter         (512) 892-0494
     Blue Jean Computer Engineering
     2609 Choctaw Trail
     Austin, TX 78745
 
 
     I am a professional engineer with a background in hardware, software,
and microprocessor design, and am a member of IEEE and ACM.  For almost a
decade I have worked for myself, and for the past few years much of that
time has been spent on independent research and development.  
 
     Some time ago, I began the construction a cryptographic software
module, which rapidly turned into a major project.  Since I had no
background in cryptographic design, the project called for a lot of
research.  I proposed many cryptographic mechanisms, and discarded most,
but two, each based generally on the shuffle algorithm (see Knuth II),
seemed both promising and new.  Extensive research finally picked up a
limited reference to one of the mechanisms (Secure Speech Communications,
Beker and Piper, 1985, Academic Press: London/Orlando, pp. 91-101). 
 
     I have named these designs "dynamic substitution" and "dynamic
transposition;" they can be described as types of "cryptographic combiner." 
A cryptographic combiner is intended to reversibly mix two data sources
(often plaintext and a pseudo-random sequence) to produce a complex result
(often pseudo-random ciphertext).  Since Vernam's time (before 1918) such
mixing has generally been done with addition mod-2, which is also known as
the exclusive-OR function.  But exclusive-OR allows access to the pseudo-
random sequence under a "known plaintext" attack, while my combiners seem
to provide better protection.  The combiners are also interesting for their
relationship to the classical methods of substitution and transposition. 
Along with a cryptographic random number generator, a combiner can produce
a simple encryption or decryption design.  
 
     This package includes the Turbo Pascal 5.5 source code and the
resulting compiled .EXE code for two programs: DYNSUB and DYNTRAN.  There
is a discussion of the algorithms in the DYNDOC.TXT file.  The programs
have been cut down as much as possible to make the cryptographic parts as
visible as possible.  While the programs do encipher (and decipher) files,
various simplifications make them unsuitable for serious cryptographic
work.  The programs are intended to be examples of the mechanisms, and to
provide a basis for comparison with previous techniques.  
 
     Naturally I would be interested in comments on the general techniques
involved, any known previous work with these mechanisms, and any weaknesses
found in them, by U.S. "snail mail," please.    
 
SHAR_EOF
fi
exit 0
#	End of shell archive
-- 
Terry Ritter    {texbell,att,cs.utexas.edu,sun!daver}!inebriae!terry
                terry at inebriae.WLK.COM  or attmail!inebriae!terry



More information about the Alt.sources mailing list