In this example, rows will be inserted by key. If the insert is successful, no further action is required. If the row is already in the table, the insert will not be done. Instead, the row will be replaced. To save another search, the replace can be done using the COUNT value set by the insert command. At the end of processing, the table will be stored and the generation number printed.
Note:
If multiple users could be updating a table—whether online, in a Read/Write VTS-TSR or other multitasking environment—be aware that a LOCK-LATCH password can be used to ensure exclusive access to a table.
In COBOL
PROCEDURE DIVISION.
HOUSE-KEEPING.
MOVE 'OW' TO xxxx-COMMAND
CALL 'TBLBASE' USING TB-PARM
xxxx-COMMAND-AREA
xxxx-PASSWORD
GENERATION
PERFORM WHILE THERE-IS-MORE-INPUT-DATA
* (obtain data for next row)
MOVE DATA-AREA TO xxxx-ROW-FIELDS
MOVE DATA-KEY TO xxxx-ROW-KEY
*** INSERT A ROW USING ITS KEY.
MOVE 'IK' TO xxxx-COMMAND
CALL 'TBLBASE' USING TB-PARM
xxxx-COMMAND-AREA
xxxx-ROW-AREA
IF xxxx-FOUND = 'N'
*** ROW FOUND SO NOT INSERTED. REPLACE INSTEAD.
MOVE 'RC' TO xxxx-COMMAND
CALL 'TBLBASE' USING TB-PARM
xxxx-COMMAND-AREA
xxxx-TABLE-ROW
END-IF
END-PERFORM
.
E-O-J.
*** END OF PROCESSING. SAVE UPDATED TABLE.
MOVE 'ST' TO xxxx-COMMAND
CALL 'TBLBASE' USING TB-PARM
xxxx-COMMAND-AREA
*** DETERMINE CURRENT TABLE CHARACTERISTICS.
MOVE 'GD' TO xxxx-COMMAND
CALL 'TBLBASE' USING TB-PARM
xxxx-COMMAND-AREA
xxxx-DEFINITION-BLOCK
DISPLAY 'GENERATION OF TABLE1 CREATED IS ' xxxx-ABS-GEN-NO
*** CLOSE THE TABLE.
MOVE 'CL' TO xxxx-COMMAND.
CALL 'TBLBASE' USING TB-PARM
xxxx-COMMAND-AREA
.
In C
#include <stdio.h>
#include <string.h>
#include <stdlib.h>
#include "dkh.h"
/*
* DK1TEX1C
*
* Update an existing table
*/
/*
* Assume these are user inputs.
*/
static char szTableName[6] = "AARON";
static char szStatus[6] = "NYYYN";
static char szWritePassword[2] = " ";
static int nGen = 0;
static char szKey[4] = "Pat";
static char szRow[21] = "Pat 123456789012345";
int main(void)
{
TbParmStruct tbParm;
TbCommandAreaStruct tbCommArea;
TbTableDefinitionStruct tbTableDef;
char sWritePassword[8];
char sStatus[8];
char sTableName[8];
int nGeneration = nGen;
char * pKeyArea = NULL;
char * pRowArea = NULL;
/*
* Initialize the parameters.
*/
fixStringLength( szTableName, sTableName, 8 );
InitTbParm( &tbParm );
InitTbCommandArea( &tbCommArea, sTableName );
InitTableDef( &tbTableDef );
/*
* Initialize tableBASE with CS, ChangeStatus.
*/
fixStringLength( szStatus, sStatus, 8 );
memcpy( tbCommArea.tbCommand, "CS", 2 );
TBLBASE( &tbParm, &tbCommArea, sStatus );
if( tbCommArea.tbError != TB_SUCCESS )
{
printf( "CS\n");
printf( "Found code: %c\n", tbCommArea.tbFound );
printf( "Error code: %d\n", tbCommArea.tbError );
printf( "Sub code: %d\n", tbCommArea.tbErrorSubcode );
return tbCommArea.tbError;
}
/*
* Call tableBASE with OW, OpenforWrite.
*/
fixStringLength( szWritePassword, sWritePassword, 8 );
memcpy( tbCommArea.tbCommand, "OW", 2 );
TBLBASE( &tbParm, &tbCommArea, sWritePassword, nGeneration);
if( tbCommArea.tbError != TB_SUCCESS )
{
printf( "OW\n");
printf( "Found code: %c\n", tbCommArea.tbFound );
printf( "Error code: %d\n", tbCommArea.tbError );
printf( "Sub code: %d\n", tbCommArea.tbErrorSubcode );
return tbCommArea.tbError;
}
/*
* GD, get table definition to retrieve the row length
* and the key length.
*/
memcpy( tbCommArea.tbCommand, "GD", 2 );
TBLBASE( &tbParm, &tbCommArea, &tbTableDef, nGeneration );
if( (tbCommArea.tbError != TB_SUCCESS)
|| (tbCommArea.tbFound == 'N') )
{
printf( "GD\n");
printf( "Found code: %c\n", tbCommArea.tbFound );
printf( "Error code: %d\n", tbCommArea.tbError );
printf( "Sub code: %d\n", tbCommArea.tbErrorSubcode );
return tbCommArea.tbError;
}
/*
* Allocate space for a row and a key.
*/
pRowArea = (char *) malloc( tbTableDef.rowSize );
if( pRowArea == NULL )
return TB_ERROR;
memset( pRowArea, ' ', tbTableDef.rowSize);
pKeyArea = (char *) malloc( tbTableDef.keySize );
if( pKeyArea == NULL ) {
free( pRowArea );
return TB_ERROR;
}
memset( pKeyArea, ' ', tbTableDef.keySize );
fixStringLength( szKey, pKeyArea, tbTableDef.keySize );
fixStringLength( szRow, pRowArea, tbTableDef.rowSize );
/*
* Call tableBASE with IK, InsertByKey.
*/
memcpy( tbCommArea.tbCommand, "IK", 2 );
TBLBASE( &tbParm, &tbCommArea, pRowArea, pKeyArea);
if( tbCommArea.tbFound == 'Y' )
{
/*
* Call tableBASE with RC, ReplacebyCount.
*/
memcpy( tbCommArea.tbCommand, "RC", 2 );
TBLBASE( &tbParm, &tbCommArea, pRowArea);
if( tbCommArea.tbError != TB_SUCCESS )
{
printf( "RC\n");
printf( "Found code: %c\n", tbCommArea.tbFound );
printf( "Error code: %d\n", tbCommArea.tbError );
printf( "Sub code: %d\n", tbCommArea.tbErrorSubcode );
free( pRowArea );
free( pKeyArea );
return tbCommArea.tbError;
}
}
/*
* Call tableBASE with ST, StoreTable.
*/
memcpy( tbCommArea.tbCommand, "ST", 2 );
TBLBASE( &tbParm, &tbCommArea );
if( tbCommArea.tbError != TB_SUCCESS )
{
printf( "ST\n");
printf( "Found code: %c\n", tbCommArea.tbFound );
printf( "Error code: %d\n", tbCommArea.tbError );
printf( "Sub code: %d\n", tbCommArea.tbErrorSubcode );
free( pRowArea );
free( pKeyArea );
return tbCommArea.tbError;
}
memcpy( tbCommArea.tbCommand, "GD", 2 );
TBLBASE( &tbParm, &tbCommArea, &tbTableDef, nGeneration );
if( (tbCommArea.tbError != TB_SUCCESS)
|| (tbCommArea.tbFound == 'N') )
{
printf( "GD\n");
printf( "Found code: %c\n", tbCommArea.tbFound );
printf( "Error code: %d\n", tbCommArea.tbError );
printf( "Sub code: %d\n", tbCommArea.tbErrorSubcode );
free( pRowArea );
free( pKeyArea );
return tbCommArea.tbError;
}
else
{
printf( "Generation of %s table: %d\n",
szTableName, tbTableDef.generations );
}
/*
* Call tableBASE with CL, CLoseTable.
*/
memcpy( tbCommArea.tbCommand, "CL", 2 );
TBLBASE( &tbParm, &tbCommArea );
if( tbCommArea.tbError != TB_SUCCESS )
{
printf( "CL\n");
printf( "Found code: %c\n", tbCommArea.tbFound );
printf( "Error code: %d\n", tbCommArea.tbError );
printf( "Sub code: %d\n", tbCommArea.tbErrorSubcode );
free( pRowArea );
free( pKeyArea );
return tbCommArea.tbError;
}
if( pRowArea != NULL )
free( pRowArea );
if( pKeyArea != NULL )
free( pKeyArea );
return TB_SUCCESS;
}
In PL/I
%process s list map compile xref attributes limits( extname(30) );
%process aggregate options object compile list map xref;
%process arch(10);
SMPLISRT: proc options(main noexecops);
/**************************************************************/
/* This program demonstrates how to update the rows for an */
/* existing table. */
/* */
/* Rows are read from input cards (SYSIN). */
/* */
/* If a record is found, the row is replaced. */
/* If a record is not found, the row is inserted. */
/* */
/* When all records have been read and the table updated, */
/* the table is stored and the rows from the new generation */
/* of the table displayed. */
/* */
/**************************************************************/
declare
tblbase external entry options(asm);
dcl sysin file record sequential input env(recsize(80));
dcl pliretc builtin;
dcl rundate char(17) date('YYYYMMDDHHMISS999');
/* */
/* row area for table */
/* */
declare
1 tablerow,
2 lastname char(20),
2 firstname char(14),
2 restofdata char(28) init((14)'HA');
declare
1 tablerow_input,
2 lastname char(20),
2 firstname char(14),
2 restofdata char(31),
2 filler char(15);
declare
1 key,
2 key1 char(20),
2 key2 char(14);
on endfile(sysin) goto on_label;
/* */
/* tbparmsp contains the PL/I copybooks for TBPARM and TB-COMMAND */
/* and can be found in your distribution library */
/* */
%include tbparmsp;
/*------------------------------------------------------*/
/* Main procedure */
/*------------------------------------------------------*/
open file (sysin);
call processtables;
call storetable;
call closetable;
put list ('return code = ', tb_error ) skip;
return;
/*------------------------------------------------------*/
/* Handle condition End-of-file for SYSIN */
/*------------------------------------------------------*/
on_label: begin;
call storetable;
call closetable;
put list ('return code = ', tb_error ) skip;
return;
end on_label;
/*------------------------------------------------------*/
/* open table and then call processtran proc */
/*------------------------------------------------------*/
processtables: proc;
call opentable;
/* process input cards */
if (tb_error = 0) then
call processtrans;
end processtables;
/*------------------------------------------------------*/
/* Read input records from SYSIN DD */
/* Insert row using key if not found on table */
/* Replace row if it already exists */
/*------------------------------------------------------*/
processtrans: proc;
do while (1 = 1);
read file(sysin) into (tablerow_input) ;
tb_command_code = 'IK';
tablerow.lastname = tablerow_input.lastname ;
tablerow.firstname = tablerow_input.firstname ;
tablerow.restofdata = tablerow_input.restofdata ;
call tblbase (tb_parm,
tb_command,
tablerow);
select ;
when ((tb_found = 'Y') | (tb_found = 'y'))
do;
tb_command_code = 'RC';
call tblbase (tb_parm,
tb_command,
tablerow);
if (tb_error > 0) then
call error_report;
else
put list('Replaced ::',tablerow_input ) skip;
end;
when (tb_found = 'N')
do;
if (tb_error = 0) then
do;
put list('Inserted ::',tablerow_input ) skip;
end;
else
call error_report;
end;
otherwise
;
end;
end;
end processtrans;
/*------------------------------------------------------*/
/* Open EXAMPLE table for write. */
/* Check TB-ERROR-CODE after OW */
/*------------------------------------------------------*/
opentable: proc;
tb_command_code = 'OW';
tb_table = 'EXAMPLE';
call tblbase(tb_parm,tb_command);
if (tb_error = 0) then
;
else
do;
put list('SMPLISRT program failed to open table ') skip;
call error_report;
end;
end opentable;
/*------------------------------------------------------*/
/* Issue table CLose command */
/* Check TB-ERROR-CODE after CL */
/*------------------------------------------------------*/
closetable: proc;
tb_command_code = 'CL';
tb_table = 'EXAMPLE';
call tblbase(tb_parm,tb_command);
if (tb_error = 0) then
;
else
do;
put list('SMPLISRT program failed to close table ') skip;
call error_report;
end;
end closetable;
/*------------------------------------------------------*/
/* Store table. Check if store is successful and */
/* do a GD command to display new generation number */
/*------------------------------------------------------*/
storetable: proc;
tb_command_code = 'ST';
tb_table = 'EXAMPLE';
call tblbase(tb_parm,tb_command);
if (tb_error = 0) then
do;
tb_command_code = 'GD';
tb_table = 'EXAMPLE';
call tblbase(tb_parm,tb_command,tb_definition_block);
put list('Store ok, new gen no:',tb_abs_gen_no) skip(3);
end;
else
do;
put list('SMPLISRT program failed to Store table', tb_table)
skip;
call error_report;
end;
end storetable;
/********************************************************
Print error information: error code and sub-code returned
for command code and table name
********************************************************/
error_report: proc;
put list('tb_command_code:', tb_command_code) skip;
put list('tb_table:', tb_table) skip;
put list('tb_error :', tb_error ) skip;
put list('tb_error_subcode:', tb_error_subcode) skip;
end error_report;
end SMPLISRT;
/*------------------------------------------------------*/