View previous topic :: View next topic
|
Author |
Message |
Muralikrishnan_Ram
New User
Joined: 28 May 2012 Posts: 6 Location: India
|
|
|
|
Hi,
I need to write a generic 9 byte (Numeric) Sequence number generator program. This unique Sequence number is going to be stored it in a table.
The flow of the program is below mentioned,
1) Select the maximum value of the table and increment it.
Select max(Col1)
from table1.
2) Insert into the table.
This works fine for the batch. When i thought to implement the same logic in online.
If i implement this logic in online,
if a two users using same online program concurrently for generating a 9 byte unique sequence number then
i may fell into this below scenarios,
a) If the table have maximum value as 000000100 then for both user will get 000000101 and trying to insert it.
however it can be handled during insert, if there is second row inserting then it will be throw a sqlcode -803 and again the second user who missed(failed) it need to try the same transaction again.
So to make it in general i would need to change the logic in batch also.
Whether there is any other way to make the sequence number in generic to both online and batch application ?
Code: |
PROCEDURE DIVISION.
0000-MAIN-LOGIC.
EXEC SQL
SELECT MAX(PART_NUMBER)
INTO
:WS-SEQ-NUM
FROM COST_TABLE1
FOR READ ONLY
END-EXEC
EVALUATE SQLCODE
WHEN 0
COMPUTE WS-TEMP-SEQ-NUM = WS-SEQ-NUM + 1
END-COMPUTE
PERFORM 1000-INSERT-TABLE THRU
1000-EXIT
WHEN OTHER
MOVE +16 TO WS-ABEND-CODE
MOVE SQLCODE TO WS-DB2-SQLCODE
MOVE '0000' TO WS-DB2-PARA
END-EVALUATE
GOBACK.
0000-EXIT.
EXIT.
1000-INSERT-TABLE.
MOVE WS-TEMP-SEQ-NUM TO
COS-PART-NUMBER
EXEC SQL
INSERT INTO COST_TABLE1
(
PART_NUMBER
,COST
)
VALUES
(
:COS-PART-NUMBER
,:COS-COST
)
END-EXEC
EVALUATE SQLCODE
WHEN 0
CONTINUE
WHEN OTHER
MOVE +16 TO WS-ABEND-CODE
MOVE SQLCODE TO WS-DB2-SQLCODE
MOVE '1000' TO WS-DB2-PARA
END-EVALUATE
.
1000-EXIT.
EXIT
.
|
Output:-
Code: |
PART_NUMBER COST
INTEGER DECIMAL(11,2)
-PKEY1----- -------------
****** **************************
000001 1 +222.00 |
|
|
Back to top |
|
|
dbzTHEdinosauer
Global Moderator
Joined: 20 Oct 2006 Posts: 6966 Location: porcelain throne
|
|
|
|
1. generic? it is anything but. it is a very specific value based on the existing max value.
2. why not have the same module that 'calculates the next sequence no'
CALLed by both batch and cics?
As far as batch, there is no need to have a separate routine,
because someone from the online could be working at the same time as the batch job.
i.e. loop on -803.
and, why SELECT, add, INSERT?
just insert max + 1.
what are the rules on 999999999 + 1?
billion - 1 is not uncommon these days.
and i image the sequence no (part no) is a decimal.
should be large integer.
PLUS, THIS IS A DB2 QUESTION. WHY IS IT IN COBOL? |
|
Back to top |
|
|
Pandora-Box
Global Moderator
Joined: 07 Sep 2006 Posts: 1592 Location: Andromeda Galaxy
|
|
|
|
Have a field with Latest_sq_used something like that .
Update this field what was the last sequence + 1 that is being generated so the program which is going to need the next sequence can read from this field next time will pick the sequence from there.
So the first run you might need insert a static data
Just a thought |
|
Back to top |
|
|
Bill O'Boyle
CICS Moderator
Joined: 14 Jan 2008 Posts: 2501 Location: Atlanta, Georgia, USA
|
|
|
|
Write a small called Assembler sub-program (can be used in Batch or On-Line), passing a 9-Byte Display-Numeric parm as well a 24-Byte workarea (for re-entrancy), which issues a Store-Clock into a Doubleword, then load the Doubleword into an 8-Byte register (LG), followed by a CVDG (Convert to Decimal Grande) into a 16-Byte Quadword, ensure the Quadword-sign nibble is 'F' and finally, unpack the Quadword into the 9-Byte Display-Numeric parm.
I can guarantee you that the returned-value in the 9-Byte parm will be unique 99.99% of the time.
The Doubleword and Quadword are composed of the 24-Byte workarea passed from the Caller. |
|
Back to top |
|
|
Naish
New User
Joined: 07 Dec 2006 Posts: 82 Location: UK
|
|
Back to top |
|
|
Muralikrishnan_Ram
New User
Joined: 28 May 2012 Posts: 6 Location: India
|
|
|
|
Thank you for replying Dick!
Dick, Yes The above piece of code which i have tried can be called in batch and CICS.But still my program is a Table specific(COST_TABLE1).
The Requirement is to write a Generic module which needs to populate 9 byte value for inserting a key for any clustering index for a DB2 table.
As per the requirement it wont available for that count( APPROXIMATELY 9,999,999). Hence 9 byte will be hold good for our requirement.
I tried it with DB2, but even accomplishing it with cobol or anyother solutions will be good. Going forward i will post it appropriately. |
|
Back to top |
|
|
Muralikrishnan_Ram
New User
Joined: 28 May 2012 Posts: 6 Location: India
|
|
|
|
Thanks Pandora, the suggestion provided is of table specific.
The Requirement is to write a Generic module which needs to populate 9 byte value for inserting a key for any clustering index for a DB2 table. |
|
Back to top |
|
|
Muralikrishnan_Ram
New User
Joined: 28 May 2012 Posts: 6 Location: India
|
|
|
|
Thanks Bill,
As i am new to the assembler level coding, i googled it and went through some of the assembler language manuals.
1) IBM High Level Assembler for MVS & VM & VSE Release 5
2) IBM High Level Assembler for MVS & VM & VSE
Release 2 Presentation Guide
It would be of great help if you could provide me with any other manuals or guidance for me to start with assmbler level coding. |
|
Back to top |
|
|
dbzTHEdinosauer
Global Moderator
Joined: 20 Oct 2006 Posts: 6966 Location: porcelain throne
|
|
|
|
is this sequence no in the high order portion of the key?
do you need a random sequence no
or
a sequenced number based on table?
or
an unused no that is > last sequence generated.
random unique you will not get from Bill's solution.
the only way you will be 100percent certain that the sequence no generated has not been used before is to have some control over
the sequence no generated in relation to sequence no's previously generated.
you prattle on about generic and not specific to a table,
yet you showed in your opening post,
the INSERT SQL, which is not generic, it is specific to a table.
I think that you are deluding yourself in thinking billion - 1 is enough.
today, next year maybe, but it a couple of years you better be working at a new site,
because i have seen this "oh, a billion is more than enough"
bite many applications in the ass.
some could solve it by going negative, some could roll and start from 1 again,
but many were caught in a trap created by their own optimism.
sorta like voting for obama and thinking things would get better |
|
Back to top |
|
|
GuyC
Senior Member
Joined: 11 Aug 2009 Posts: 1281 Location: Belgium
|
|
|
|
just define the column as
- identifier if it has to be unique per table
- sequence if it has to be unique . |
|
Back to top |
|
|
Muralikrishnan_Ram
New User
Joined: 28 May 2012 Posts: 6 Location: India
|
|
|
|
The requirement is to create a random unique number and also that the previously used number should not be used again . It should be unique always. |
|
Back to top |
|
|
dick scherrer
Moderator Emeritus
Joined: 23 Nov 2006 Posts: 19243 Location: Inside the Matrix
|
|
|
|
Hello,
Quote: |
The requirement is to create a random unique number and also that the previously used number should not be used again . |
Who came up with such a "requirement" and why is there some need for it to be random?
If this is across multiple tables/keys how will you know if the "number" has been used elsewhere or has been used but later deleted?
It sounds like there is a rather major design flaw in this way of thinking.
Suggest you reread whay GUYC has provided. |
|
Back to top |
|
|
Craq Giegerich
Senior Member
Joined: 19 May 2007 Posts: 1512 Location: Virginia, USA
|
|
|
|
Muralikrishnan_Ram wrote: |
The requirement is to create a random unique number and also that the previously used number should not be used again . It should be unique always. |
Random and unique are conflicting requirements. |
|
Back to top |
|
|
dbzTHEdinosauer
Global Moderator
Joined: 20 Oct 2006 Posts: 6966 Location: porcelain throne
|
|
|
|
The TS is caught in a trap.
if he uses the concept provided by GuyC
(and incidentally used by most professional IT shops throughout the planet)
his module is not needed
also, the notion of adding new rows at various 'random' positions has been proven - BS.
New rows (inserted) should not be out-of-sequence with the basic key.
we used to take a timestamp, and move 1 for 4 to the end, 20-26 to the begining,
(there were other idiot attempts at spacing out additional rows)
but it has been proven that it saves nothing,
helps nowhere,
and in general a waste of cycles to create this randomness.
old BS design. |
|
Back to top |
|
|
Muralikrishnan_Ram
New User
Joined: 28 May 2012 Posts: 6 Location: India
|
|
|
|
It is not going to be used across multiple tables. It should be a random but unique number generator. It will be called to generate unique numbers concurrently . |
|
Back to top |
|
|
dbzTHEdinosauer
Global Moderator
Joined: 20 Oct 2006 Posts: 6966 Location: porcelain throne
|
|
|
|
Muralikrishnan_Ram wrote: |
It is not going to be used across multiple tables. It should be a random but unique number generator. It will be called to generate unique numbers concurrently . |
WTF does that mean?
like arguing politics with a 'progressive'.
ignore facts, change the requirements with each post,
but,
i imagine this is just some poor guy given a requirement by
jerks held in 1990's methodology. |
|
Back to top |
|
|
Pandora-Box
Global Moderator
Joined: 07 Sep 2006 Posts: 1592 Location: Andromeda Galaxy
|
|
|
|
Take the current timestamp and remove dots and dashes and apend with 1 billionth of a second |
|
Back to top |
|
|
enrico-sorichetti
Superior Member
Joined: 14 Mar 2007 Posts: 10888 Location: italy
|
|
|
|
the topic is just becoming a useless waste of resources
will be locked in a while |
|
Back to top |
|
|
Naish
New User
Joined: 07 Dec 2006 Posts: 82 Location: UK
|
|
|
|
Experts, as I have previously mentioned-
Quote: |
Wouldn't CREATE SEQUENCE help?
Experts please correct me if I am wrong. |
Won't selecting the NEXT VALUE of the SEQUENCE help?
One of our teams will soon be changing one of the systems with such a design for online to avoid contention. Could you guide me if this would go wrong some how. As far as I see this looks promising. |
|
Back to top |
|
|
dick scherrer
Moderator Emeritus
Joined: 23 Nov 2006 Posts: 19243 Location: Inside the Matrix
|
|
|
|
Hello,
For whatever reason, there is a belief that the number needs to be random.
What business reason might there be for such a "requirement"? |
|
Back to top |
|
|
agkshirsagar
Active Member
Joined: 27 Feb 2007 Posts: 691 Location: Earth
|
|
|
|
OP did not put his requirement correctly. Truly random numbers can't be unique by definition.
There is an intrinsic function in COBOL to generate random numbers. Also, there is DB2 function RAND that provides this same functionality.
Read the manual my friend!
Esentially, OP is looking for a semaphore like mechanism to avoid contention. I fully agree with Naish that it can be achieved with DB2 SEQUENCES. |
|
Back to top |
|
|
Bill O'Boyle
CICS Moderator
Joined: 14 Jan 2008 Posts: 2501 Location: Atlanta, Georgia, USA
|
|
|
|
Here's the example sub-program I had described -
Code: |
*PROCESS RENT PROGRAM IS RE-ENTRANT
***********************************************************************
*---------------------------------------------------------------------*
* *
* THIS SUB-PROGRAM CAN BE CALLED FROM BATCH OR ON-LINE COBOL *
* AND RETURNS THE DECIMAL EQUIVILENT OF AN 8-BYTE 'STCK' AS *
* 9-BYTES, PACKED-DECIMAL SIGNED. *
* *
* WHEN CALLED FROM CICS, THE CALLER NEEDS TO USE CICS 'ENQ' *
* BEFORE THE CALL AND CICS 'DEQ' AFTER THE CALL, ENSURING *
* SERIALIZATION. *
* *
* WHEN CALLED FROM BATCH, THIS SUB-PROGRAM WILL ISSUE MVS *
* 'ENQ/DEQ' MACROS, ENSURING SERIALIZATION. *
* *
* THIS SUB-PROGRAM DETERMINES THE RUN-ENVIRONMENT, SO THERE'S *
* NO NEED TO PASS THIS INFORMATION. *
* *
* NOTE THE 88-BYTES AFTER THE HALFWORD RETURN-CODE. THIS STG *
* IS NECESSARY FOR RE-ENTRANCY AND IS REQUIRED IN A CICS *
* ENVIRONMENT. *
* *
* EXAMPLE SYNTAX: *
* *
* 03 WS-RANDOM-PARM. *
* 05 WS-RANDOM-NBR PIC S9(17) PACKED-DECIMAL. *
* 05 WS-RANDOM-RTNCODE PIC 9(04) BINARY. *
* 88 WS-RANDOM-SUCCESS VALUE ZERO. *
* 05 FILLER PIC X(88). *
* 03 WS-RANDOM PIC X(08). VALUE 'RANDOM'. *
* *
* CALL WS-RANDOM USING WS-RANDOM-PARM. *
* *
*---------------------------------------------------------------------*
***********************************************************************
STGDSECT DSECT CALLER-STG (R7)
USING *,R7 INFORM ASSEMBLER
STGAREA DS 0XL88 DYNAMIC-STG WORKAREA (FROM CALLER)
QUADWORD DS L ALIGNED-QUADWORD
REGSAVEA DS XL72 REGISTER-SAVEAREA
PRMDSECT DSECT PARMAREA (R9)
USING *,R9 INFORM ASSEMBLER
PRMAREA DS 0XL11 PARMAREA FROM CALLER
PRMRNDOM DS PL9 PARM RANDOM-NBR (PACKED-DECIMAL)
PRMRETCD DS XL2 PARM RETURN-CODE (HWORD)
RANDOM CSECT
USING *,R3 INFORM ASSEMBLER
SAVE (14,12) SAVE REGISTERS
LA R3,0(,R15) CSECT-ADDRESSABILITY
B ADDRPARM ADDRESS THE PARMAREA
********
******** ASSEMBLY DATE/TIME 'EYECATCHER'
********
EYECTCHR DS 0CL46
DC CL46' <<< ASSEMBLY DATE/TIME: &SYSDATC/&SYSTIME..00 >>>'
ORG EYECTCHR+6 REDEFINITION
DC X'A2A285948293A8' LOWER-CASE 'SSEMBLY'
ORG EYECTCHR+15 REDEFINITION
DC X'81A385' LOWER-CASE 'ATE'
ORG EYECTCHR+20 REDEFINITION
DC X'899485' LOWER-CASE 'IME'
ORG EYECTCHR+L'EYECTCHR RESET LOCATION-KTR
DC CL1' ' SEPARATOR-SPACE
********
******** CONSTANTS USED IN 'BATCH' ONLY
********
ENQNAME DS 0CL18
DC CL18'$$RANDOM/ENQ/DEQ$$'
ORG ENQNAME+3 REDEFINITION
DC X'8195849694' LOWER-CASE 'ANDOM'
ORG ENQNAME+10 REDEFINITION
DC X'9598' LOWER-CASE 'NQ'
ORG ENQNAME+14 REDEFINITION
DC X'8598' LOWER-CASE 'EQ'
ORG ENQNAME+L'ENQNAME RESET LOCATION-KTR
DC CL1' ' SEPARATOR-SPACE
ENQRES DC 0CL24
DC CL24'$$RANDOM/NBR/GENERATOR$$'
ORG ENQRES+3 REDEFINITION
DC X'8195849694' LOWER-CASE 'ANDOM'
ORG ENQRES+10 REDEFINITION
DC X'8299' LOWER-CASE 'BR'
ORG ENQRES+14 REDEFINITION
DC X'8595859981A39699' LOWER-CASE 'ENERATOR'
ORG ENQRES+L'ENQRES RESET LOCATION-KTR
DC CL1' ' SEPARATOR-SPACE
********
******** BEGIN EXECUTION
********
ADDRPARM DS 0H
L R9,0(,R1) PARMAREA-ADDRESSABILITY
LA R9,0(,R9) CLEAR TOP-BIT
XC PRMAREA,PRMAREA ENSURE X'00'S
OI PRMRNDOM+L'PRMRNDOM-1,X'0C'
LA R7,L'PRMAREA(,R9) STORAGE-ADDRESSABILITY
XC STGAREA,STGAREA ENSURE X'00'S
LA R15,REGSAVEA POINT TO OUR 'RSA'
ST R13,4(,R15) BACKWORD-CHAIN
ST R15,8(,R13) FORWARD-CHAIN
LR R13,R15 POINT TO OUR 'RSA'
L R15,X'21C' ADDRESS CURRENT TCB
L R15,X'D0'(,R15) ADDRESS TCB EXTN
L R15,X'14'(,R15) ADDRESS AFCB
LTR R15,R15 BATCH-ENVIRONMENT?
BZ BATCHENQ YES, ISSUE BATCH 'ENQ'
CLC =CL3'AFC',0(R15) BATCH-ENVIRONMENT?
BNE BATCHENQ YES, ISSUE BATCH 'ENQ'
XR R2,R2 ENSURE X'00'S FOR 'CICS'
B STCKRQST REQUEST FOR 'STORE-CLOCK'
BATCHENQ EQU *
LA R2,16 SET TO NON-ZERO FOR 'BATCH'
ENQ (ENQNAME,ENQRES,E,L'ENQRES,SYSTEMS),RET=NONE
STCKRQST EQU *
MVC PRMRETCD,=AL2(4095) LOAD 'INVALID' RETURN-CODE
STCK QUADWORD REQUEST FOR 'STORE-CLOCK'
OC QUADWORD,QUADWORD VALID NON-ZERO VALUE?
BZ CHKRNENV NO, CHECK RUN-ENVIRONMENT
XC PRMRETCD,PRMRETCD ENSURE 'VALID' RETURN-CODE
LG R1,QUADWORD PREPARE FOR 'CVDG'
LPGR R1,R1 ENSURE IT'S POSITIVE
CVDG R1,QUADWORD MAKE IT 16-BYTES DECIMAL
OI QUADWORD+L'QUADWORD-1,X'0F'
ZAP PRMRNDOM,QUADWORD POPULATE AS A PL9
CHKRNENV EQU *
LTR R2,R2 CICS ENVIRONMENT?
BZ RTN2CLLR YES, RETURN TO THE CALLER
DEQ (ENQNAME,ENQRES,L'ENQRES,SYSTEMS),RET=NONE
RTN2CLLR EQU *
L R13,4(,R13) RESTORE CALLER'S R13
MVC QUADWORD(L'PRMRETCD),PRMRETCD
LH R15,QUADWORD LOAD AS HWORD
XC STGAREA,STGAREA ENSURE X'00'S
RETURN (14,12),RC=(15) RESTORE AND RETURN
LTORG ,
YREGS ,
RANDOM AMODE 31
RANDOM RMODE ANY
END ,
|
Note that lower-case letters are constructed using ORG (Redefines) statements, so that some "goof ball" doesn't come along, issue a CAPS ON and accidentally hits a line where lower-case letters have been specified. I know this, because I've done it many times.
I understand that you need a 9-Byte Display-Numeric value, but the sub-program returns a 9-Byte (PIC S9(17) COMP-3) value, so you can possibly develop a method to choose different digits for your Display-Numeric field? It's good to have choices.
Usage instructions can be found in the comments. Must be Assembled/Linked as AMODE(31), RMODE(ANY).
And yes, I'm still stuck on using 8-Byte labels or less.
HTH.... |
|
Back to top |
|
|
|