-- XeroxDecompressImpl.mesa
-- Copyright (C) Xerox Corporation 1984, 1985. All rights reserved.
-- Last edited by castillo      18-Apr-85 13:47:12

-- This module implements the decompression algorithm for scanned image in IMG
-- format. The algorithm is described in detail in the document by PSD
-- "Xerox Printing System Interface Standard, Xerox integration Standard"

DIRECTORY
  Decompress USING [DecompressInfo, Done, Init, NextLine],
  Environment USING [bitsPerWord],
  Heap USING [Create, FreeNode, MakeNode],
  Inline USING [BITAND, BITSHIFT, BITXOR, LongCOPY, LowHalf];

XeroxDecompressImpl: PROGRAM
  IMPORTS Heap, Inline
  EXPORTS Decompress =
  BEGIN

-- ================

  nBits: CARDINAL = Environment.bitsPerWord;
  nNibs: CARDINAL = 4;  -- Number of nibbles in a word
  bitGotMask: ARRAY [0..nBits) OF CARDINAL = [
    177777B, 77777B, 37777B, 17777B, 7777B, 3777B, 1777B, 777B, 377B, 177B, 77B,
    37B, 17B, 7B, 3B, 1B];
  bitGetMask: ARRAY [0..nBits] OF CARDINAL = [
    0, 1B, 3B, 7B, 17B, 37B, 77B, 177B, 377B, 777B, 1777B, 3777B, 7777B, 17777B,
    37777B, 77777B, 177777B];

  maxLINCount: CARDINAL = 15;

    -- Encoding
  axx: ARRAY [0..4) OF CARDINAL = [8, 4, 2, 1];
  enc: CARDINAL = 2;    -- ENC mode
  eoi: CARDINAL = 113;  -- End of image
  htn: CARDINAL = 3;    -- HTN mode
  lin: CARDINAL = 1;    -- LIN mode
  raw: CARDINAL = 0;    -- Raw (ie., no encoding)
  soi: CARDINAL = 112;  -- Start of image

-- ============

  WrdPtr: TYPE = LONG POINTER TO WORD;

  BitPosition: TYPE = RECORD [
    bufPtr:   WrdPtr ← NIL,  -- Word pointer 
    bitBuf:   CARDINAL ← 0,  -- Current bit buffer
    bitPos:   CARDINAL ← 0,  -- Current bit position within BitBuf
    bitCount: LONG CARDINAL ← 0  -- Bit count
    ];

  BitPositionPtr: TYPE = LONG POINTER TO BitPosition;
  
-- ================ used for Statictics

  DecompressStat: TYPE = RECORD [
    total:	LONG CARDINAL,
    compressed:	LONG CARDINAL,
    raw:	CARDINAL,
    enc:	CARDINAL,
    lin:	CARDINAL,
    htn:	CARDINAL];

  --encLines: CARDINAL	← 0;   ENC mode line count
  --htnLines: CARDINAL	← 0;   HTN mode line count
  --linLines: CARDINAL	← 0;   LIN mode line count
  --rawLines: CARDINAL	← 0;   RAW mode line count

-- ================

  inputPos:   BitPosition ← [];  -- Current input position
  samplePos:  BitPosition ← [];  -- Current position in sample buffer
  currLinePos:BitPosition ← [];  -- Bit position of current scan line in sample
  pvLinePos:  BitPosition ← [];  -- Bit position of last scan line in the sample
  bufferPtr:  WrdPtr ← NIL;      -- ptr to buffer for previous line
  zeroBuffPtr: LONG POINTER TO ARRAY [0..0) OF WORD ← NIL;
  scanLength:  CARDINAL	← 0;   -- Scan length of input
  scanBitLen:  CARDINAL	← 0;   -- Scan length of output in bits
  scanWordLen: CARDINAL	← 0;   -- Scan length in words
  nRange:   CARDINAL	← 0;
  scnLine:  CARDINAL	← 0;   -- Count of scan lines
  linCount: CARDINAL	← 0;   --  # of consecutive LIN mode
  nextMode: CARDINAL	← 0;
  
  eoiFound: BOOLEAN ← FALSE;
  
  
  decZone: UNCOUNTED ZONE ← Heap.Create [initial: 1];
  
-- ==================

  Error: PUBLIC ERROR [line: CARDINAL] = CODE;

-- ===================

  GetN: PROCEDURE [bits: INTEGER, pos: BitPositionPtr ← @inputPos]   -- GetNibble
        RETURNS [val: CARDINAL] =
  BEGIN OPEN i: pos↑;
    -- Will get bits from buffer "pointed" to by pos. If pos is not given, the
    -- buffer pointer is inputPos (ie., compressed pixel array buffer).
    remainder: INTEGER;
    currPos: INTEGER ← i.bitPos + bits;  -- current bit position
    i.bitCount ← i.bitCount + bits;  -- update current bit count
    remainder ← nBits - currPos;
    -- Processing is funtion of resulting buffer word position
    SELECT TRUE FROM
      (remainder > 0) =>  -- Incomplete
        BEGIN
        val ← Inline.BITSHIFT[i.bitBuf, -remainder];
        i.bitBuf ← Inline.BITAND[i.bitBuf, bitGetMask[remainder]];
        i.bitPos ← currPos;
        END;
      (remainder = 0) =>  -- Full
        BEGIN
        val ← i.bitBuf;
        i.bufPtr ← i.bufPtr + 1;
        i.bitBuf ← i.bufPtr↑;
        i.bitPos ← 0;
        END;
      ENDCASE =>  -- Overflow
        BEGIN
        remPos: INTEGER ← nBits + remainder;
        i.bitPos ← -remainder;
        i.bufPtr ← i.bufPtr + 1;
        val ←
          Inline.BITSHIFT[i.bitBuf, i.bitPos] + Inline.BITSHIFT[
            i.bufPtr↑, -remPos];
        i.bitBuf ← Inline.BITAND[i.bufPtr↑, bitGetMask[remPos]];
        END;
  END;  -- GetN


  PutN: PROCEDURE [val: CARDINAL, bits: INTEGER] =
  BEGIN OPEN s: samplePos;
    -- This routine will put bits into the sample buffer
    -- ("pointed" to by samplePos).     
    remainder: INTEGER;
    currPos: INTEGER ← s.bitPos + bits;  -- current bit position
    s.bitCount ← s.bitCount + bits;  -- update current bit count
    remainder ← nBits - currPos;
    -- Processing is funtion of resulting buffer word position
    SELECT TRUE FROM
      (remainder > 0) =>  -- Incomplete
        BEGIN
        s.bitBuf ← s.bitBuf + Inline.BITSHIFT[val, remainder];
        s.bitPos ← currPos;
        END;
      (remainder = 0) =>  -- Full
        BEGIN
        s.bufPtr↑ ← s.bitBuf + val;
        s.bufPtr ← s.bufPtr + 1;
        s.bitBuf ← 0;
        s.bitPos ← 0;
        END;
      ENDCASE =>  -- Overflow
        BEGIN
        s.bitPos ← -remainder;
        s.bufPtr↑ ← s.bitBuf + Inline.BITSHIFT[val, remainder];
        s.bitBuf ← Inline.BITSHIFT[val, nBits - s.bitPos];
        s.bufPtr ← s.bufPtr + 1;
        END;
  END;  -- PutN
    

  SetInputPos: PROCEDURE[oldPos: BitPosition] RETURNS[newPos:BitPosition] = INLINE
  BEGIN
    -- This procedure will reset the given bit position for input (
    -- i.e., set bitBuf to the value currently stored).
    newPos ← oldPos;
    newPos.bitBuf ← Inline.BITAND[newPos.bufPtr↑, bitGotMask[newPos.bitPos]];
  END;  -- SetInputPos


  ProcessHTN: PROCEDURE = INLINE
  BEGIN -- This routine will process the HTN mode line.
    pvRange: CARDINAL ← 0;
    currRange: CARDINAL ← 0;
    currLineGet: BitPosition;
    bits: CARDINAL ← scanBitLen;
      -- set input and output to start of current line
    samplePos ← currLinePos;
    currLineGet ← SetInputPos[currLinePos];
    WHILE bits >= nRange DO
        pvRange ← Inline.BITXOR[GetN[nRange, @currLineGet], pvRange];
        PutN[pvRange, nRange];
        bits ← bits - nRange;
        ENDLOOP;
      -- get rid of remainder
    IF bits > 0 THEN 
       PutN[Inline.BITXOR[ 
	       GetN[bits, @currLineGet],
	       Inline.BITSHIFT[pvRange, INTEGER[bits] - nRange]], bits];
    --htnLines ← htnLines + 1;
  END;  -- ProcessHTN


  ProcessLIN: PROCEDURE = INLINE
  BEGIN  -- Process scan line encoded in LIN mode.
    currPtr: WrdPtr ← currLinePos.bufPtr;
    pvPtr: WrdPtr ← pvLinePos.bufPtr;
      -- set input and output to start of current line. This routine will assume
      -- that the scan line will start and end on a word boundary. PutN is not 
      -- used for efficiency. XOR every byte
    FOR i: CARDINAL IN [0..scanWordLen) DO
        currPtr↑ ← Inline.BITXOR[currPtr↑, pvPtr↑];
        currPtr ← currPtr + 1;
        pvPtr ← pvPtr + 1;
        ENDLOOP;
      --linLines ← linLines + 1;
  END;  -- ProcessLIN


  PutZerosAndNibble: PROCEDURE [n: CARDINAL, nibble: CARDINAL] = {
     FOR i: CARDINAL IN [0..n) DO PutN[0, 4]; ENDLOOP; PutN[nibble, 4] };


  PutManyZeros: PROCEDURE [count: CARDINAL] =
  BEGIN  OPEN s: samplePos;
    -- This routine will put zeros into sample buffer.  Should be
    -- only used for large number of zero bits.
    rem: CARDINAL;
    IF count <= nBits THEN {PutN[0, count]; RETURN;};
    IF s.bitPos # 0 THEN {
       count ← count - (nBits - s.bitPos); -- update count
       PutN[0, nBits - s.bitPos] }; -- word align
    Inline.LongCOPY[zeroBuffPtr, count/nBits, s.bufPtr];
    s.bufPtr ← s.bufPtr + count/nBits;
    rem ← count MOD nBits;
    s.bitCount ← s.bitCount + count - rem; -- update bit count
    IF rem # 0 THEN PutN[0, rem];
  END; -- PutManyZeros    


  PutManyZerosAndNibble: PROCEDURE [n: CARDINAL, nibble: CARDINAL] = INLINE
  BEGIN
      -- Just Like PutZerosAndNibble except PutN is not used for zero nibbles for
      -- efficiency
      PutManyZeros[n * 4]; PutN[nibble, 4];
  END;

  ZeroFill: PROCEDURE = INLINE
  BEGIN -- Zero fill the rest of the line.  PutN is not used for efficiency.
     PutManyZeros[
        scanBitLen - (Inline.LowHalf[samplePos.bitCount - currLinePos.bitCount])];
  END;
  
   
  MoveLines: PROCEDURE = INLINE
  BEGIN OPEN s: samplePos;
    -- This routine will move lines from input to output.
    ptr: WrdPtr ← s.bufPtr;
    FOR i: CARDINAL IN [0..scanLength / nBits) DO
      ptr↑ ← GetN[nBits];
      ptr ← ptr + 1;
      ENDLOOP;
   s.bufPtr ← ptr;
   s.bitCount ← s.bitCount + scanLength;
   IF scanBitLen # scanLength THEN PutN[0, scanBitLen - scanLength];
  END; -- MoveLines


  CompressedNextLine: PUBLIC Decompress.NextLine =
  -- PROC [h: DecompressHandle, out: LONG POINTER] RETURNS [valid: BOOLEAN] --
  BEGIN ENABLE UNWIND => CompressedDone[h];
    code: CARDINAL;
    mode: CARDINAL;
    nibble: CARDINAL;
    t: INTEGER;
    IF eoiFound THEN RETURN [FALSE];
    -- Initialize sample position used by PutN
    samplePos.bitPos ← 0;
    samplePos.bitBuf ← 0;
    samplePos.bufPtr ← out;
    samplePos.bitCount ← 0;
    currLinePos ← samplePos;  -- start at sample[0]
    pvLinePos ← [bufferPtr, 0,0,0];  -- remember start of previous line
    mode ← nextMode;
    IF mode > 3 THEN ERROR Error[--badLCC,-- scnLine];
      -- Decode: fill up next scan line of samples with scanLength
      -- decode values.
    IF mode = raw THEN {
       MoveLines[];
       --rawLines ← rawLines + 1;
       nextMode ← GetN[8]}  -- next LCC or EOI
    ELSE {  -- Decode
        DO  -- get run
          code ← GetN[4];
          IF (8 <= code) AND (code <= 11) THEN
             PutZerosAndNibble[0, axx[code MOD 4]]  -- 4-bit codes
          ELSE {  -- 8-bit codes
            code ← code * 16 + GetN[4];  -- form 8-bit code
            IF code = soi THEN ERROR Error[--badSOI,-- scnLine];
            IF (code <= 3) OR (code = eoi) THEN GOTO GotAllRuns
            ELSE IF (4 <= code) AND (code <= 147B) THEN
                    PutZerosAndNibble[code / 4, axx[code MOD 4]]
                 ELSE IF (150B <= code) AND (code <= 177B) THEN {
                         t ← (code / 2) MOD 16;
			 IF t = 4 THEN PutZerosAndNibble[code MOD 2, 3]
			 ELSE PutZerosAndNibble[code MOD 2, t]}
                      -- 200B <= code <= 277B are covered by 4-bit codes 
                      ELSE {  --300B <= code <= 377B: 12 bit codes
		           g: CARDINAL ← Inline.BITAND[code, 77B];
			   nibble ← GetN[4];
			   IF nibble = 0 THEN {
			      IF g = 0 THEN PutN[0, 4]
			      ELSE PutManyZerosAndNibble[(100B * g) - 1, 0]}
                           ELSE PutZerosAndNibble[g, nibble]}
            };  -- 8 bit codes

          REPEAT
            GotAllRuns =>
              BEGIN
              nextMode ← code;
              IF samplePos.bitCount - currLinePos.bitCount > scanLength THEN
                ERROR Error[--lineTooLong,-- scnLine];
              ZeroFill[];  -- Fill Scan line with 0's
              END;  -- GotAllRuns
          ENDLOOP;  -- get run
         };  -- Decode

    -- Reconstruct
    SELECT mode FROM
        lin => {
          linCount ← linCount + 1;
          IF linCount > maxLINCount THEN ERROR Error[--tooManyLIN,-- scnLine];
          ProcessLIN[];
          };
        htn => {linCount ← 0; ProcessHTN[]; };
        enc => {linCount ← 0; --encLines ← encLines + 1-- };
        ENDCASE => linCount ← 0;

    scnLine ← scnLine + 1;
    Inline.LongCOPY[from: out, nwords: scanWordLen, to: bufferPtr];
    IF nextMode = eoi THEN eoiFound ← TRUE;
    valid ← TRUE;
  END;   -- CompressedNextLine


  CompressedInit: PUBLIC Decompress.Init =
  -- PROCEDURE [v: Environment.Block] RETURNS [h: DecompressHandle] --
  BEGIN ENABLE UNWIND => decZone.FREE[@h];
    reserved: CARDINAL;
    eoiFound ← FALSE;
    h ← decZone.NEW[Decompress.DecompressInfo];
    h.flavor ← compressed;
    h.private ← @v;
    -- Initialize input position used by GetN
    inputPos.bitPos ← IF (v.startIndex MOD 2) = 0 THEN 0 ELSE 8;
    inputPos.bufPtr ← LOOPHOLE[v.blockPointer + v.startIndex/2];
    inputPos.bitBuf ← inputPos.bufPtr↑;
    inputPos.bitCount ← 0;

    -- Initialize other statistic variables
    -- rawLines ← encLines ← linLines ← htnLines ← 0;
    
    scnLine ← 0;
    reserved ← GetN[16];
    nRange ← GetN[16];
    scanLength ← GetN[16];
    IF (reserved # 0) OR (nRange < 5) OR (scanLength MOD 8 # 0) THEN
       ERROR Error[--badHeader,-- scnLine];
    -- Force output to end on word boundary (For efficiency).
    scanWordLen ← (scanLength + nBits - 1) / nBits;
    scanBitLen ← scanWordLen * nBits;
    -- cause an error if 1st line is LIN
    linCount ← maxLINCount + 1;
    IF GetN[8] # soi THEN ERROR Error[--noSOI,-- scnLine];
    nextMode ← GetN[8];  -- first LCC
    bufferPtr ← Heap.MakeNode[decZone, scanWordLen];
    zeroBuffPtr ← Heap.MakeNode[decZone, scanWordLen];
    FOR i: CARDINAL IN [0..scanWordLen) DO zeroBuffPtr[i] ← 0; ENDLOOP;
    h.scanLength ← scanLength;
  END;  -- CompressedInit


  CompressedDone: PUBLIC Decompress.Done =
  -- PROCEDURE [h: DecompressHandle] --
  BEGIN
    decZone.FREE[@h];
    Heap.FreeNode[decZone, bufferPtr];
    Heap.FreeNode[decZone, zeroBuffPtr];
    --stat ← [
    --  samplePos.bitCount,inputPos.bitCount,rawLines,encLines,linLines,htnLines];
  END;


  END...

LOG  
 8Mar84 - Okamoto - Created.
16Nov84 - castillo - renamed to XeroxDecompressImpl; moved around to make use of the Decompress interface.
 4Jan85 - castillo - updated to new parm in Init, byte alignment assumed; added eoiFound.
18Apr85 - castillo - stuffed scanLength in handle at Init time.