-- Em3270CmdProcessPack.mesa   

-- Revised for Star 3.3H by Lui:	 7-May-84 17:33:21 
-- Owner:  Lui 

-- Overview:
--   Em3270CmdProcessPack provides two main functions: 
--    1) Syntax and address validation of the input stream from the IBM Host.
--    2) Execute incoming commands and orders from the IBM Host .
--   CheckSyntax examines each character in the input stream sequentially to ensure that all commands and orders in the command stream appear in the correct sequence,
--    and any buffer address specified must be in the valid range. The first error encounter would cause an ERROR SyntaxError to be raised. The module which called this
--    procedure is expected to catch this error and delete the input stream.
--   ProcessCommands executes each command and order as it is encounter by calling the appropriate Buffer Manager rountine.
--   Notes: Since the whole input stream must be correct before it is executed, the Main buffer will always contain accurate info.
--          The translation of displayable data from host character set to WSCharacter Set is done right before the data is pass to the Buffer Manager.
  

DIRECTORY
  CharDefs USING [Char],
  Em3270BufferDefs USING [bufferSize, ClearBuffer, DisplayBuffer, EraseAllUnprotected, EraseUnprotectedToAddress, GetBufferAddress, InsertCursor,   
        ProgramTab, Release, RepeatToAddress, Reserve, ResetAllModified, SetBufferAddress, StartField, UpdateStatus, WriteBlock],
  Em3270CharTransDefs USING [OISCharFromEBCDIC, OISRunFromEBCDIC],  
  Em3270CmdProcessDefs,
  Em3270ComDefs USING [DoStreamPut],
  Em3270PrivDefs,
  Em3270StatusDefs,
  Em3270UserInputDefs USING [DoReadMod, AIDCodes, AIDVal, Reset, ResetAIDStatus],
  GateStream USING [readModified3270],
  Inline USING [BITAND],
  NqDefs USING [EnqueueBackgroundSynch],
  NtDefs USING [Pvsynch],
  SchemaDefs USING [Lschema, lschemaNil],
  StandardDefs,
  ToneDefs,
  ZoneMgrDefs USING [GetPredefinedZone];
  
Em3270CmdProcessPack: PROGRAM 
  IMPORTS
    Em3270BufferDefs, Em3270CharTransDefs, Em3270ComDefs, Em3270PrivDefs, Em3270StatusDefs,
    Em3270UserInputDefs, Inline, NqDefs, ToneDefs, ZoneMgrDefs
    
  EXPORTS Em3270CmdProcessDefs, Em3270PrivDefs =

  BEGIN OPEN Em3270CmdProcessDefs, Em3270PrivDefs, StandardDefs;
  -- ====================
  --     Types 
  -- ====================
  LptCmdData: TYPE = LONG POINTER TO CmdData;
  CmdData: PUBLIC TYPE = RECORD [
    lschemaWn: SchemaDefs.Lschema ← SchemaDefs.lschemaNil,
    bufMgrHandle: LptBufferData ← LOOPHOLE[LONG[NIL]],
    ixWnArr: CARDINAL,   -- associate an element of the global window status array with this instance of 3270.
    comBufIndex: ComBufIndexCt ← 0,    -- index to input stream's buffer
    bytesProcessed: CARDINAL ← 0,                   -- total number of bytes exeamined.
    prevCmd: Em3270CmdProcessDefs.Command ← nullChar,    -- previous command in the input stream
    bvChained: Bv ← FALSE,     --  SST chained and unchained is no longer used, we'll always recieved the SST unchain, the reason is due to the fix for AR 9143 of Services. The CheckSyntax will now need to decide and remember whether the input contain chained or unchained commands.   
    stopIndexPlusOne: CARDINAL ← 0,          -- total number of bytes in the input stream
    lptInputBuf: LptBufOfChar ← NIL,
    lptToTransFile: BaseOISToEFile,
    bvAlarm: Bv ← FALSE,     -- sound alarm at end of current command.
    bvUnlock: Bv ← FALSE,  -- unlock keyboard and reset status area.
    sTextChunkPtr: LptTextRun ← NIL,  -- pointer to a run of CharDefs.Char text. by keeping it in the instance data, avoid the need to keep allocating and freeing.  
    eTextChunkPtr: LptETextRun ← NIL, -- pointer to a run of EBCDIC text. by keeping it in the instance data, avoid the need to keep allocating and freeing.
    bvCkBufFormat: Bv ← FALSE,    --   If text was entered into buffer, Must update status(check to see if buffer is formatted) of buffer at end of that command. 
    bvTextRun: Bv ← FALSE];     --  True => command block just recieved contains text. Call Em3270BufferDefs.DisplayBlock only if true.
    
  AqCmdCtxt: TYPE = RECORD [
    bufferMgrHandle: LptBufferData ← LOOPHOLE[LONG[NIL]],
    ixWnStatus: CARDINAL];
  lptrCmdCtxt: TYPE = LONG POINTER TO AqCmdCtxt;
    
  -- =======================
  --      Constants
  -- =======================
  maxWn: CARDINAL = 8;    -- assume the maximum number of 3270 window one can open is 8.   It is actually only 6 due to STAR'S physical display.

  -- =======================
  --      Global variables
  -- =======================
  cmdZone: UNCOUNTED ZONE ← ZoneMgrDefs.GetPredefinedZone[session];
   
  -- wnClose was added because if the user closes the 3270 window while we have already EnqueueBackgroundSynch(recieved data to be displayed in the 3270 window), Star would crash. the CLOSE process have higher priority than the EnqueueBackgroundSynch process.
  wnClose: ARRAY[0..maxWn) OF Bv ← ALL[TRUE];    -- if the window is closed, we want to nullify any display that we have send to EnqueueBackgroundSynch. 
  ixwnClose: CARDINAL ← 0;    
 
  SyntaxError: PUBLIC ERROR = CODE;
  Underflow: ERROR = CODE;
  InsufficentCharacter: ERROR = CODE;
  NoEscapePrecedesCommand: ERROR = CODE;
  IllegalCommand: ERROR = CODE;
  IllegalAddress: ERROR = CODE;
  IllegalOrder: ERROR = CODE;
  EAUBeforeWrite: ERROR = CODE;
    
  -- =======================

  CreateCmd: PUBLIC PROC[lptBufferData: LptBufferData, lschemaWn: SchemaDefs.Lschema, 
    lptToTransFile: BaseOISToEFile] RETURNS[cmdHandle: LptCmdData] =
    BEGIN
    -- alocates spaces for instance data. stores its corresponding instance of buffer manager.
    cmdHandle ← cmdZone.NEW[CmdData];
    cmdHandle.bufMgrHandle ← lptBufferData;
    cmdHandle.lschemaWn ← lschemaWn;
    cmdHandle.lptToTransFile ← lptToTransFile;
    UNTIL wnClose[ixwnClose] = TRUE DO   -- register itself with in the global data.  
      ixwnClose ← (ixwnClose+1) MOD maxWn;
    ENDLOOP;
    wnClose[ixwnClose] ← FALSE;
    cmdHandle.ixWnArr ← ixwnClose;     --  store the index
    ixwnClose ← (ixwnClose+1) MOD maxWn;
    END;
    
  DestroyCmd: PUBLIC PROC[cmdHandle: LptCmdData] =
    BEGIN
    -- Deallocate Command processor's instance data.
    -- we have to free up the space for ctxtCmd here also.
    wnClose[cmdHandle.ixWnArr] ← TRUE;
    cmdZone.FREE[@cmdHandle];
    END;  
    
  CheckSyntax: PUBLIC PROC[my: LptCmdData, lptGetBuf: LptBufOfChar, totalBytePlusOne: CARDINAL] =
    BEGIN
    -- syntax and address validation. 
    ENABLE 
      BEGIN
      InsufficentCharacter, NoEscapePrecedesCommand, IllegalCommand, IllegalAddress, IllegalOrder, EAUBeforeWrite =>  
         {  Em3270StatusDefs.DisplayCode[lschema: my.lschemaWn, code: Em3270StatusDefs.Code[programCheck]];  
	    GOTO exit;   };
      END;
      
    my.comBufIndex ← 0;
    my.bytesProcessed ← 0;
    my.prevCmd ← Em3270CmdProcessDefs.nullChar;
    my.bvChained ← FALSE;
    my.stopIndexPlusOne ← totalBytePlusOne;
    my.lptInputBuf ← lptGetBuf;
    
    UNTIL  ( my.bytesProcessed >= my.stopIndexPlusOne ) DO
      IF my.prevCmd # Em3270CmdProcessDefs.nullChar THEN
        my.bvChained ← TRUE;    -- the input is a chained command.
      ValidateCommand[my];
    ENDLOOP;
    EXITS
      exit => ERROR SyntaxError;  -- whoever calls this procedure should catch this error. 
    END;   --CheckSyntax 
    
    
  GetChar: PROC[my: LptCmdData] RETURNS[char: CHARACTER] =
    BEGIN
    -- Get next byte from the input buffer
    IF my.bytesProcessed < my.stopIndexPlusOne THEN
       BEGIN
       IF my.comBufIndex = LAST[ComBufIndexCt] THEN  -- at end of current buffer 
          BEGIN
	  my.lptInputBuf ← my.lptInputBuf.nextBuf;
	  my.comBufIndex ← 0;
	  END;
       char ← GetCharInternal[my];
       END
    ELSE  ERROR  Underflow;         -- at end of input stream.      
    END;      -- GetChar
	
  GetCharInternal: PROC[my: LptCmdData] RETURNS[char: CHARACTER] = INLINE 
    BEGIN
    char ← my.lptInputBuf.hostData[my.comBufIndex];
    my.comBufIndex ← my.comBufIndex + 1;
    my.bytesProcessed ← my.bytesProcessed + 1;
    END;       -- GetCharInternal
    
  UndoGetChar: PROC[my: LptCmdData] = INLINE
    BEGIN
    my.bytesProcessed ← my.bytesProcessed - 1;
    my.comBufIndex ← my.comBufIndex - 1;
    END; 
   
  ValidateCommand: PROC[my: LptCmdData] =
    BEGIN
    -- expecting the bytes EBCDIC.ESC COMMAND in the input stream.
    -- EBCDIC.ESC always precede an IBM host command
    OPEN Em3270CmdProcessDefs;
    ENABLE 
      Underflow  => ERROR InsufficentCharacter;
    char: CHARACTER;        
    SELECT char ← GetChar[my] FROM 
      CommandSeparator => 
         SELECT char ← GetCommand[my] FROM 
           eraseAllUnprotected => ValidateEAU[my];
	   eraseWrite => ValidateEraseWrite[my];
	   eraseWriteAlternate => ValidateEWA[my];
	   write => ValidateWrite[my];
	   readModified => my.prevCmd ← Em3270CmdProcessDefs.readModified;  -- Read Modified commands should not include any data or orders. 
           ENDCASE => ERROR IllegalCommand    -- expecting to see a command
      ENDCASE => ERROR NoEscapePrecedesCommand   -- each command must be preceded by the EBCDIC.ESC byte
    END;  --  ValidateCommand;
    
    
  ValidateEAU: PROC[my: LptCmdData] = INLINE
    BEGIN
    -- an EraseAllUnprotected cannot come before any type of a write command. 
    my.prevCmd ← Em3270CmdProcessDefs.eraseAllUnprotected;
    END;
    
  ValidateEraseWrite: PROC[my: LptCmdData] = INLINE
    BEGIN
    -- EraseWrite cannot come after an EraseAllUnprotected command  
    IF my.prevCmd = Em3270CmdProcessDefs.eraseAllUnprotected THEN
      ERROR EAUBeforeWrite
    ELSE 
      BEGIN
      my.prevCmd ← Em3270CmdProcessDefs.eraseWrite;
      ValidateWriteCommon[my];   
      END;
    END;
    
    
  ValidateEWA: PROC[my: LptCmdData] = INLINE
    BEGIN
    -- EraseAllUnprotected cannot come after an EraseAllUnprotected command
    IF my.prevCmd = Em3270CmdProcessDefs.eraseAllUnprotected THEN
      ERROR EAUBeforeWrite
    ELSE 
      BEGIN
      my.prevCmd ← Em3270CmdProcessDefs.eraseWriteAlternate;
      ValidateWriteCommon[my];
      END;
    END;
    
    
  ValidateWrite: PROC[my: LptCmdData] = INLINE
    BEGIN
    -- Write cannot come after the EraseAllUnprotected command 
    IF my.prevCmd = Em3270CmdProcessDefs.eraseAllUnprotected THEN
      ERROR EAUBeforeWrite
    ELSE 
      BEGIN
      my.prevCmd ← Em3270CmdProcessDefs.write;
      ValidateWriteCommon[my];
      END;
    END;
    
  ValidateWriteCommon: PROC[my: LptCmdData] =
    BEGIN
    OPEN Em3270CmdProcessDefs; 
    char: CHARACTER;
    GetWCC[my];   -- any write command must be followed by a WCC; thus the byte immediately following any write will always be treated as a WCC.
    DO
      char ← GetChar[my ! Underflow => EXIT];    -- end of current and last command.   
      SELECT Em3270CmdProcessDefs.Order[char] FROM
	eraseUnprotectedToAddress => ValidateAddress[my];
	startField => ValidateStartField[my];
	setBufferAddress => ValidateAddress[my];
	programTab => NULL;
	insertCursor => NULL;
	repeatToAddress => ValidateRTA[my];
	nullChar, ge, ff, cr, nl, em, dup, fm => NULL;      -- Control characters are treated as data
	CommandSeparator => { UndoGetChar[my]; RETURN };
      ENDCASE => NULL;         -- any non command or order are treated as data. thus control character will be treated as data.
    ENDLOOP;
    END;       -- ValidateWriteCommon
      
       
  ValidateStartField: PROC[my: LptCmdData] = INLINE
    BEGIN
    -- an attribute byte always follows an StartField Order.
    GetAttribute[my];
    END;
    
   
  ValidateRTA: PROC[my: LptCmdData] = INLINE
    BEGIN
    ValidateAddress[my];   -- Repeat to address should be follow by an address(2 bytes) 
    [] ← GetChar[my];    -- this byte contains the character to be repeated
    END;
    
  GetAttribute: PROC[my: LptCmdData] = INLINE 
    BEGIN
    -- we are not interested in the content of the attribute byte at this point
    [] ← GetChar[my];
    END;
  
  GetCommand: PROC[my: LptCmdData] RETURNS[char: CHARACTER] = INLINE
    BEGIN
    char ← GetChar[my];
    END;
  
 
  GetWCC: PROC[my: LptCmdData] = INLINE
    BEGIN
    -- we are not interested in the content of the WCC byte at this point
    [] ← GetChar[my];
    END;
    
  ValidateAddress: PROC[my: LptCmdData] = INLINE
    BEGIN
    index: CARDINAL ← GetAddress[my];  
    IF index NOT IN [0..Em3270BufferDefs.bufferSize) THEN   -- is address in the valid range
      ERROR IllegalAddress;
    END;
    
  GetAddress: PROC[my: LptCmdData] RETURNS[CARDINAL] =
    BEGIN
    -- the next two bytes are interpreted as an address
    -- only the lower order 6 bits contain valid infomation in any address byte
    -- The following 3 steps will convert 2 consecutive bytes into an address 
    --  1) first turn the 2 highest order bits in both byte to 0's.
    --  2) then shift the first byte 6 bit position to the left(multiply by 64)  
    --  3) added to second byte.  
    topByte: Em3270CmdProcessDefs.Binary ← LOOPHOLE[Inline.BITAND[GetChar[my], Em3270CmdProcessDefs.AddressMask]];
    bottomByte: Em3270CmdProcessDefs.Binary ← LOOPHOLE[Inline.BITAND[GetChar[my], Em3270CmdProcessDefs.AddressMask]];
    RETURN[topByte*64+bottomByte];
    END; 
    
  DisplaySync: NtDefs.Pvsynch = {
    -- This procedure have a low process priority in Star, there exist a small window for 2 potential errors to occur:
    --  1) the user can close the window(high priority) while there are data waiting to get display in the queue. In this case an address fault would arise, because the buffer's and command processer's instance data have already been destroyed.
    --  Dur to the method that I choose to solve problem 1 described above, I have introduced another problem, i.e.
    --  2) Each instance of the 3270 window is assoicated with an element of a global array(wnClose), the problem arises when as soon as the user closes one window(while there are displayed enqueued) he opens another 3270 window(before the enqueue of the closed window get processed), he might get assigned the same element of the global array. 
    my: lptrCmdCtxt ← LOOPHOLE[ctxtsynch, lptrCmdCtxt];   
    IF ~wnClose[my.ixWnStatus] THEN {  -- only call the buffer display routine if the 3270 window is still open to avoid address fault CRASH
      Em3270BufferDefs.Reserve[my.bufferMgrHandle];   -- set lock on buffer
      Em3270BufferDefs.DisplayBuffer[my: my.bufferMgrHandle];
      Em3270BufferDefs.Release[my.bufferMgrHandle] };   -- remove lock on buffer 
    cmdZone.FREE[@my];    -- the window has already gone away, so free up the space. 
     };  -- of DisplaySync
    
  
  ProcessCommands: PUBLIC PROC[my: LptCmdData, lptGetBuf: LptBufOfChar, totalBytePlusOne: CARDINAL, bvChain: BOOLEAN] =
    BEGIN
    -- execute commands and orders in the input stream
    -- Note: Starting with Services 5.0w bvChain is always false.
    ctxtCmd: lptrCmdCtxt ← NIL;
    my.comBufIndex ← 0;
    my.bytesProcessed ← 0;
    my.stopIndexPlusOne ← totalBytePlusOne;
    my.lptInputBuf ← lptGetBuf;
    my.sTextChunkPtr ← cmdZone.NEW[TextRun];  --  in almost all case a chained of command will contain some text. placing this statment here allowes us to avoid unnecessary allocation and deallocation (performance).
    my.eTextChunkPtr ← cmdZone.NEW[EBCDICTextRun];
    
    Em3270BufferDefs.Reserve[my.bufMgrHandle];   -- lock the buffer.
    UNTIL  ( my.bytesProcessed >= my.stopIndexPlusOne ) DO
      DoCommand[my];
    ENDLOOP;
    Em3270BufferDefs.Release[my.bufMgrHandle];   -- remove lock on buffer
    
    IF my.bvTextRun THEN 
      {
      ctxtCmd ← cmdZone.NEW[AqCmdCtxt];  -- AqCmdCtxt should be freed in DisplaySync.
      ctxtCmd.bufferMgrHandle ← my.bufMgrHandle;
      ctxtCmd.ixWnStatus ← my.ixWnArr;
      NqDefs.EnqueueBackgroundSynch[pvsynch: DisplaySync, ctxtsynch: ctxtCmd];           -- Update the display screen.
      };
    cmdZone.FREE[@my.sTextChunkPtr];
    cmdZone.FREE[@my.eTextChunkPtr];
    my.bvTextRun ← FALSE;
    END;   --    ProcessCommands
    
    
  DoCommand: PROC[my: LptCmdData] = 
    BEGIN 
    OPEN Em3270CmdProcessDefs;
    char: CHARACTER;
    char ← GetChar[my];        -- this char should be the ESC which precedes any command.
    char ← GetCommand[my];  -- expecting to see a command
    IF char # readModified AND my.bvChained = FALSE THEN
      Em3270BufferDefs.SetBufferAddress[my.bufMgrHandle, Em3270BufferDefs.GetBufferAddress[my.bufMgrHandle, keyMode]];  -- Current Buffer Address ← Curser Address; 
    SELECT char FROM     -- What is the command
      eraseAllUnprotected => Em3270BufferDefs.EraseAllUnprotected[my.bufMgrHandle];
      eraseWrite => DoEraseWrite[my];
      eraseWriteAlternate, write => DoWrite[my];
      readModified => { DoReadModified[my]; RETURN; };  -- +++  read modified commands does not have any WCC thus there is no need to excute any other statments
      ENDCASE => NULL;         -- it should not have fall through. Should have been caught by CheckSyntax 
      
    IF my.bvCkBufFormat THEN  -- writing any text into the buffer can cause the buffer to be unformmated. 
      BEGIN
      Em3270BufferDefs.UpdateStatus[my.bufMgrHandle];  -- should this be done after each command or at end of the whole chain of command. This PROC needs to be called  only if text was recieved. ie. the procedure WriteBlock or WriteChar of Bufferdefs was called.
      my.bvCkBufFormat ← FALSE;
      END;
      
    IF my.bvAlarm THEN ToneDefs.MakeTone[tone: ToneDefs.warning];  -- sound audio alarm
    IF my.bvUnlock THEN ResetStatus[my];  -- should this be done after each command, or at end of a chain of commands?
    END;       -- DoCommand
    
  ResetStatus: PROC[my: LptCmdData] = 
    BEGIN
    -- the keyboard restore is (bit 6) = 1 => On need to reset status area and reset AID and free the buffers used for the previous Com.Put
    Em3270UserInputDefs.Reset[my.lschemaWn];     -- this procedure actually does all of the above.(great)
    END;
    
    
  DoReadModified: PROC[my: LptCmdData] = 
    BEGIN
    -- check the current state of AID to determmine if we are in a normal state or retry state. Retry state means resent whatever was previously sent to the host. Normal state means send to the host the modified fields that are currently in the buffer. The search for modified field starts at buffer address 0 if the buffer is unformmated or the read command is unchained or it is chained from a copy, select, sense, or no operation. Start the search at current buffer address if the command sis chained from a write, erase write, read modified, read modified all, or read buffer. This proc does not change the current AID value. 
    bvNoAID: Bv ← GetAIDStatus[my.lschemaWn];   
    putMDTStream: MDTStream ← GetMDTStream[my.lschemaWn];
    IF bvNoAID THEN {  --  collect modified fields, the buffer mgr automically overrides the start search address if the buffer is unformatted.
      IF ~my.bvChained THEN   -- unchained => start at address 0
        Em3270UserInputDefs.DoReadMod[my.lschemaWn, my.bufMgrHandle, putMDTStream.lptbuf, Em3270UserInputDefs.AIDCodes[noAID], keyMode]
      ELSE   --  Start search at current buffer address.
        Em3270UserInputDefs.DoReadMod[my.lschemaWn, my.bufMgrHandle, putMDTStream.lptbuf, Em3270UserInputDefs.AIDCodes[noAID], hostMode];
      Em3270UserInputDefs.ResetAIDStatus[my.lschemaWn]; }
    ELSE   --  retry state: send the old stuff
      Em3270ComDefs.DoStreamPut[
        my: GetComHandle[my.lschemaWn], mdtStream: putMDTStream,
        sstType: GateStream.readModified3270];
    IF GetInputStatus[my.lschemaWn] = inputInhibited THEN {  -- if X-Clock is on then change it to X-System
      Em3270StatusDefs.DisplayCode[lschema: my.lschemaWn, code: time, bvOn: FALSE];
      Em3270StatusDefs.DisplayCode[lschema: my.lschemaWn, code: systemLock, bvOn: TRUE]
      };
    END;
    
  
  DoEraseWrite: PROC[my: LptCmdData] = 
    BEGIN       
    Em3270BufferDefs.ClearBuffer[my.bufMgrHandle];  -- erase the entire buffer
    DoWrite[my];
    END;   
    
  DoWrite: PROC[my: LptCmdData] =
    BEGIN
    OPEN Em3270CmdProcessDefs;
    char: CHARACTER;
    dataPreceded: Bv ← FALSE;
    insertNull: Bv ← FALSE;
    startTransIndex: ComBufIndexCt ← 0;        -- starting index for translating to OIS character set. 
    ProcessWCC[my, GetChar[my]];   -- The next byte will always be treated as a WCC byte;
    
    DO
      char ← GetChar[my ! Underflow => EXIT ]; -- end of current command. exit DO loop and return control to ProcessCommand.
      BEGIN
	SELECT char FROM
	   eraseUnprotectedToAddress => Em3270BufferDefs.EraseUnprotectedToAddress[my.bufMgrHandle, GetAddress[my]];   -- call buffer manager's EUTA with address  
	   startField => Em3270BufferDefs.StartField[my.bufMgrHandle, GetChar[my]];    -- call buffer manager's start field with attribute char     
	   setBufferAddress => Em3270BufferDefs.SetBufferAddress[my.bufMgrHandle, GetAddress[my]];    -- set current buffer address to address specified
	   programTab => {
	      IF dataPreceded OR insertNull THEN insertNull ← TRUE;
	      insertNull ← Em3270BufferDefs.ProgramTab[my.bufMgrHandle, insertNull];       
	      IF insertNull THEN GOTO TabFailed; };	       
	   insertCursor => Em3270BufferDefs.InsertCursor[my.bufMgrHandle];      -- set cursor to Current buffer address
	   repeatToAddress => DoRTA[my];
	   CommandSeparator => { UndoGetChar[my]; RETURN };
        ENDCASE =>  { dataPreceded ← TRUE; UndoGetChar[my]; ProcessTextRun[my]; GOTO Donothing };     -- assume it is data.
	dataPreceded ← FALSE;
	insertNull ← FALSE;
	EXITS
	  TabFailed => dataPreceded ← FALSE;
	  Donothing => NULL;
      END;
    ENDLOOP;
    END; -- DoWrite
  
      
  ProcessTextRun: PROC[my: LptCmdData] = 
    BEGIN
    char: CHARACTER;
    ixChunk: TextIndexType ← 0;
    my.bvTextRun ← TRUE;
    my.bvCkBufFormat ← TRUE;
    DO
      ixChunk ← 0;
      WHILE ixChunk < MaxRunIndex DO
        char ← GetChar[my ! Underflow => GOTO NoMoreText]; 
	SELECT char FROM   -- expect to see either orders, ebcdic ESC(command seperator), or text.
	  eraseUnprotectedToAddress, startField, setBufferAddress, programTab, insertCursor, repeatToAddress, CommandSeparator =>  {
	     UndoGetChar[my]; 
	     GOTO NoMoreText };  --   
	  ENDCASE => {    --  non orders or EBCDIC escape is assume to be text.
	     my.eTextChunkPtr↑[ixChunk] ← char;
	     ixChunk ← ixChunk + 1; };
      ENDLOOP;
      -- call write block of buffer manager.
      -- filled up a chunk, there may be more; thus go back to outer loop.
      Em3270CharTransDefs.OISRunFromEBCDIC[my.lptToTransFile, my.eTextChunkPtr, my.sTextChunkPtr, ixChunk];
      Em3270BufferDefs.WriteBlock[my.bufMgrHandle, my.sTextChunkPtr, ixChunk, hostMode];
      REPEAT
	NoMoreText => {
	  IF ixChunk > 0 THEN 
	    BEGIN
	    Em3270CharTransDefs.OISRunFromEBCDIC[my.lptToTransFile, my.eTextChunkPtr, my.sTextChunkPtr, ixChunk];
	    Em3270BufferDefs.WriteBlock[my.bufMgrHandle, my.sTextChunkPtr, ixChunk, hostMode];  -- we still have data, call write block of buffer manager.
	    END;
	  };    		-- this text run is complete.
    ENDLOOP;
    END;   -- ProcessTextRun
   
     
  DoRTA: PROC[my: LptCmdData] = 
    BEGIN
    oisChar: CharDefs.Char;
    addr: CARDINAL ← GetAddress[my];
    char: CHARACTER ← GetChar[my];
    my.bvCkBufFormat ← TRUE;
    my.bvTextRun ← TRUE;
    oisChar ← Em3270CharTransDefs.OISCharFromEBCDIC[my.lptToTransFile, char];
    Em3270BufferDefs.RepeatToAddress[my.bufMgrHandle, oisChar, addr];
    END;
    
  ProcessWCC: PROC[my: LptCmdData, WCC: CHARACTER] =
    BEGIN
    -- if sound alarm(bit 5) = 1 then sound alarm at end of operation. 
    -- if reset mdt(bit 7) = 1 then reset all mdt before any data is written or orders are executed. 
    -- if keyboard restore is (bit 6) = 1 then call status Defs to clear system lock and set system availbale. at completion of current command
    --    by calling Em3270UserInputDefs.Reset[my.lschemawn, special3270Reset]
    alarmMask: CHARACTER = 4C;
    mdtMask: CHARACTER = 1C;
    lockMask: CHARACTER = 2C;
    my.bvAlarm ← (alarmMask = Inline.BITAND[alarmMask, WCC]);
    my.bvUnlock ← (lockMask = Inline.BITAND[lockMask, WCC]);
    IF (mdtMask = Inline.BITAND[mdtMask, WCC]) THEN
      Em3270BufferDefs.ResetAllModified[my.bufMgrHandle];
    END;
          
   
END.
LOG
14-Jan-82 15:37:53        -- Lui          - Created          
18-Jan-82 16:25:12        -- Lui          - Added ProcessCommands
25-Jan-82  8:38:13        -- Lui          - Added ProcessTextSequenec
13-Feb-82 16:12:13        -- Lui          - Added DestroyCmd, CreateCmd 
18-Feb-82 15:14:00        -- Lui          - Added Em3270PrivDefs
24-Feb-82 17:37:11        -- Lui          - Added ProcessWCC 
1-Mar-82 11:02:55	  -- Kernaghan	  - Fix erors and Stub for Star22.2
16-Mar-82 14:45:52	  -- Kernaghan	  - Reserve/Release in DisplaySync.
19-Mar-82 11:25:05        -- Lui          - edited RTA code
2-Apr-82 13:19:39         -- Lui          - edited calls to BufferPack's WriteBlock to always use hostMode, and set CBA ← cursorAddress for unchained commands (fixed AR #6326)
15-Jun-82 15:33:58        -- Lui          - Changed the following procedures to INLINE procedure. GetCharInternal, UndoGetChar, ValidateEAU, ValidateEraseWrite, ValidateEWA, ValidateWrite, ValidateStartField, ValidateRTA, GetAttribute, GetCommand, GetWCC, ValidateAddress.        
15-Jun-82 17:30:17        -- Lui          - added a call to Em3270BufferDefs.UpdateStatus at exit of ProcessCommands.
18-Jun-82 11:39:11        -- Lui          - changed code in ProcessTextRun to call OISRunFromEBCDIC instead of OISCharFromEBCDIC.     					 16-Jul-82 18:26:42        -- Lui          - moved Em3270BufferDefs.UpdateStatus from ProcessCommands to DoCommand.  
19-Jul-82 10:12:01        -- Lui          - Added sTextChunkPtr and eTextChunkPtr to instance data, and move allocation of space to hold text coming from host to ProcessCommands instead of in ProcessTextRun.
 4-Aug-82 14:58:20        -- Lui         - merge with Star2.1ar
 9-Aug-82 14:29:44       -- Lui          - modify ValidateWriteCommon, DoWrite, and ProcessTextRun to accept IBM control characters as data, This is neccessary because the ECS does pass unexpected control characters to Star.
25-Aug-82 13:11:24       -- Lui          - added lang to CreateCmd, and to instance data.   
30-Aug-82 12:02:05       -- Lui          - fix closing window while there are still data enqueued for display bug. added global array wnClose   
31-Aug-82 17:04:54       -- Lui          - added my.lang to all references of Em3270CharTransDefs  
 9-Sep-82 17:15:13       -- Lui          - changed lang to lptToTransFile
26-Jan-83 16:14:13       -- Lui          - CheckSyntax will now decide if input contains chained or unchained command.
29-Apr-83 10:28:57       -- Lui          - AR 14821: BoundsFault with wnClose[ixwnClose].
30-Jun-83 14:00:23       -- Lui          - support for Read Modified.
 7-May-84 17:33:28       -- Lui          - AR: 4830: add test for turning X-Clock into X-System DoReadModified.