View previous topic :: View next topic
|
Author |
Message |
jerryte
Active User

Joined: 29 Oct 2010 Posts: 205 Location: Toronto, ON, Canada
|
|
|
|
I am coding a program to generate a list of random 15 digit numbers. COBOL has a RANDOM function but it requires a seed number. I can use the current time to create a seed on the first call. However if by a slim chance the program is run at the exact same time on different days then it will create the same sequence of random numbers. Since this will be scheduled job to run daily it is remote but possible.
The LE callable service CEERAN0 also generates random numbers. It will generate its own seed number using "current Greenwich Mean Time".
My questions - does LE use the full date & time to create the seed? My assumption is that yes it does. If it uses just the time then it may encounter the same problem as the COBOL function.
This may be more of an IBM question. Opinions are welcome as well. |
|
Back to top |
|
 |
Bill O'Boyle
CICS Moderator

Joined: 14 Jan 2008 Posts: 2501 Location: Atlanta, Georgia, USA
|
|
|
|
How about Calling a sub-program, which issues a STCK and returns it in doubleword-binary format (default) as well as a PL16 format, with a neutral nibble 'F'? STCK values are guaranteed to be unique each time.
Code: |
*PROCESS RENT PROGRAM IS RE-ENTRANT
***********************************************************************
*---------------------------------------------------------------------*
* *
* THIS SUB-PROGRAM RETURNS THE CURRENT STORE-CLOCK VALUE TO *
* THE CALLER AND CAN BE USED IN BOTH CICS AND BATCH. THE PPT *
* EXECUTION-KEY CAN BE 'USER' OR THIS SUB-PROGRAN CAN BE *
* STATICALLY CALLED (NO PPT-ENTRY REQUIRED). *
* *
* CALL SYNTAX: *
* *
* 03 WS-GETSTCK PIC X(08) VALUE 'GETSTCK'. *
* 03 WS-GETSTCK-PARM-REC. *
* 05 WS-GETSTCK-TOD PIC S9(18) BINARY. *
* 05 WS-GETSTCK-TOD-X REDEFINES WS-GETSTCK-TOD *
* PIC X(08). *
* 05 WS-GETSTCK-PACKED PIC X(16). *
* 05 WS-GETSTCK-RSA PIC X(72). *
* 03 WS-OMITTED PIC X(01) VALUE LOW-VALUE. *
* *
* IT CAN BE CALLED IN THREE WAYS - *
* *
* 01) CALL WS-GETSTCK USING WS-GETSTCK-PARMREC *
* *
* 02) CALL WS-GETSTCK USING WS-OMITTED *
* WS-GETSTCK-PARM-REC *
* *
* 03) CALL WS-GETSTCK USING WS-OMITTED WS-OMITTED *
* WS-GETSTCK-PARM-REC *
* *
* NOTE: WS-GETSTCK-PARM-REC DOES NOT REQUIRE INITIALISATION. *
* *
* THANK YOU FOR YOUR SUPPORT.... *
* *
*---------------------------------------------------------------------*
***********************************************************************
PRINT GEN ACTIVATE MACRO EXPANSION
PRMDSECT DSECT PRMDSECT (R7)
USING *,R7 INFORM ASSEMBLER
PRMBEGIN EQU * BEGIN-PARMAREA
PRMSTCKB DS XL8 CURRENT STORE-CLOCK (BINARY)
PRMSTCKP DS PL16 CURRENT STORE-CLOCK (PACKED)
PRMRSA DS XL72 REGISTER-SAVEAREA
PRMLGTH EQU *-PRMBEGIN PARMAREA-LGTH
GETSTCK CSECT BEGIN CSECT (R3)
USING *,R3 INFORM ASSEMBLER
SAVE (14,12) SAVE REGISTERS
LA R3,0(,R15) CSECT ADDRESSABIITY
J VALIDATE VALIDATE/VERIFY PARMS-PASSED
EYECTCHR DC CL48' <<< 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-COUNTER
VALIDATE EQU *
LR R7,R1 SAVE R1 IN R7
LA R15,16 LOAD 'BAD' RETURN-CODE
L R1,0(,R1) LOAD INTO ITSELF
CLFI R1,X'FF000000' IBM 'NULL' ADDRESS?
JE RTN2CLLR YES, RETURN TO THE CALLER
LA R1,0(,R1) CLEAR TOP-BIT (FAILSAFE)
LTR R1,R1 ANY PARMS PASSED?
JZ RTN2CLLR NO, RETURN TO THE CALLER
LR R1,R7 RESTORE R1 FROM R7
L R7,0(,R1) ADDRESS 1ST-PARM
TM 0(R1),X'80' ONE-PARM PASSED?
JO ADDRPLST YES, ADDRESS PARMLIST
L R7,4(,R1) ADDRESS 2ND-PARM
TM 4(R1),X'80' TWO-PARMS PASSED?
JO ADDRPLST YES, ADDRESS PARMLIST
L R7,8(,R1) ADDRESS 3RD-PARM (DEFAULT)
ADDRPLST EQU *
LA R7,0(,R7) CLEAR TOP-BIT
XC PRMBEGIN(PRMLGTH),PRMBEGIN
LA R15,PRMRSA POINT TO OUR SAVEAREA
ST R13,4(,R15) BACKWARD-CHAIN
ST R15,8(,R13) FORWARD-CHAIN
LR R13,R15 POINT TO OUR SAVEAREA
LA R15,16 SET 'INVALID' RC
STCK PRMSTCKB GET CURRENT-STCK
JNZ RTN2CLLR NON-ZERO CONDITION-CODE, RETURN
LG R0,PRMSTCKB PREPARE FOR 'LPGR'
LPGR R1,R0 ENSURE POSITIVE VALUE
CVDG R1,PRMSTCKP MAKE IT 16-BYTES PACKED-DECIMAL
XR R15,R15 SET 'ALL IS WELL' RC
RTN2CLLR EQU *
OI PRMSTCKP+L'PRMSTCKP-1,X'0F'
L R13,4(,R13) RESTORE CALLER'S R13
XC PRMRSA,PRMRSA CLEAR OUR 'RSA'
RETURN (14,12),RC=(15) RESTORE REGISTERS AND RETURN
LTORG ,
YREGS , MVS REGISTER-EQUATE
GETSTCK AMODE 31 ,
GETSTCK RMODE ANY ,
END , END 'GETSTCK'
|
HTH.... |
|
Back to top |
|
 |
steve-myers
Active Member
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
|
|
|
|
jerryte wrote: |
... My questions - does LE use the full date & time to create the seed? My assumption is that yes it does. If it uses just the time then it may encounter the same problem as the COBOL function. ... |
Rather than waste a lot of your time posting this query, ... what does the LE manual say? It took me all of 3 minutes to find the manual and look up the CEERAN0 function. Unfortunately, it just talks about "Greenwich Mean Time." So I then found "Greenwich Mean Time" in the manual. This pointed me to CEEGMT, which has 2 outputs. CEERAN0 does not say which CEEGMT output it uses, but neither one seems appropriate; the 32 bit "Lillian" output is number of days from 14 October 1582, and the 64 bit seconds from 14 October 1582 is too large. On the other hand, if it uses the low order 32 bits of the number of seconds as the seed you will almost certainly have a unique value from day to day. |
|
Back to top |
|
 |
jerryte
Active User

Joined: 29 Oct 2010 Posts: 205 Location: Toronto, ON, Canada
|
|
|
|
Bill O'Boyle wrote: |
How about Calling a sub-program, which issues a STCK and returns it in doubleword-binary format (default) as well as a PL16 format, with a neutral nibble? STCK values are guaranteed to be unique each time. |
Thanks for the suggestion. I want to avoid using assembler. I am hoping that the CEERAN0 subroutine will do the job for me as is |
|
Back to top |
|
 |
jerryte
Active User

Joined: 29 Oct 2010 Posts: 205 Location: Toronto, ON, Canada
|
|
|
|
I think only an IBM person can provide a definitive answer by looking at the source code for CEERAN0. Does it use the full date/time to generate the seed. My assumption is that it does.
My other option is to get the date and time (using FUNCTION CURRENT-TIME) and then do calcuations using both the 10 digit year and the 8 digit time. |
|
Back to top |
|
 |
Bill O'Boyle
CICS Moderator

Joined: 14 Jan 2008 Posts: 2501 Location: Atlanta, Georgia, USA
|
|
|
|
Quote: |
Thanks for the suggestion. I want to avoid using assembler. I am hoping that the CEERAN0 subroutine will do the job for me as is |
I'm sure this is not your decision, but management's instead, as many suits look at Assembler and get hives.
Also, I think you mean FUNCTION CURRENT-DATE, which returns CCYYMMDDHHMMSSTH in bytes 01-16.
But, LE Callable Service Routine "CEELOCT" returns CCYYMMDDHHMMSSTHM, which is more finite with the milliseconds, in Byte-17.
The LE suite of Callable Routines out shine any FUNCTION in COBOL. In fact, many FUNCTION's call LE routines under the covers.
For example, FUNCTION CURRENT-DATE calls "CEELOCT" (for bytes 01-16) and "CEEGMTO (for bytes 17-21). |
|
Back to top |
|
 |
Ed Goodman
Active Member
Joined: 08 Jun 2011 Posts: 556 Location: USA
|
|
|
|
I gotta know...what are these numbers used for????
Can they be duplicates at all from day to day? As in can I have number 1111 on day 1, but then like ten days later have the same '1111' appear in a different list? |
|
Back to top |
|
 |
Bill O'Boyle
CICS Moderator

Joined: 14 Jan 2008 Posts: 2501 Location: Atlanta, Georgia, USA
|
|
|
|
Ed,
This is why a STCK will work for generating a RANDOM number as a STCK value is always unique.
Unfortunately, STCK reaches standard EPOCH (reaches its peak) in September of 2042, which would then require using STCKE. |
|
Back to top |
|
 |
jerryte
Active User

Joined: 29 Oct 2010 Posts: 205 Location: Toronto, ON, Canada
|
|
|
|
Ed Goodman wrote: |
I gotta know...what are these numbers used for????
Can they be duplicates at all from day to day? As in can I have number 1111 on day 1, but then like ten days later have the same '1111' appear in a different list? |
It will be used as a key value which is to be sent to an external vendor. The number will be stored on a db2 table along with an inhouse key value. If the vendor has a question about a record they send us the external key and then we can look up the internal record.
Extra logic will be built to query the random number on the table to ensure it was not generated previously. This will ensure it is unique.
I might try the sql RAND() function which probably works the same as the CEERAN0 callable service. |
|
Back to top |
|
 |
Bill Woodger
Moderator Emeritus
Joined: 09 Mar 2011 Posts: 7309 Location: Inside the Matrix
|
|
|
|
Is it a random-number for the same "internal key" on different days?
Code: |
Day 1
internal key 1 random A
Day 2
internal key 1 random B
Day 3
internal key 1 random C |
Unless you are sequencing the data being sent out on the random number, you're just sending a very-lightly-obfuscated sequence number, with a many-to-one mapping across days.
It that is OK, then what's wrong with just a sequence number?
Code: |
Day 1
internal key 1 sequence A
Day 2
internal key 1 sequence B
Day 3
internal key 1 sequence C |
No fear of non-unique, no extra checking needed. At the point you run out of sequence numbers, you've run out of random numbers anyway, it just takes progressively longer to find a free one (however, you'd not so much notice this with 15 digits, for a while - you've calculated how long?). |
|
Back to top |
|
 |
jerryte
Active User

Joined: 29 Oct 2010 Posts: 205 Location: Toronto, ON, Canada
|
|
|
|
Bill Woodger wrote: |
Is it a random-number for the same "internal key" on different days? |
It is a one time generation for each internal key. Both values will be stored on a db2 table for reference. Since each internal key DECIMAL(15,0) is unique we need the external random key to be unique as well.
I have discovered that a double floating point number can hold about 18 digits. I can take the random number that was generated and multiply by (10 ** 18) to get an 18 digit integer. This is the limit for a COBOL number.
Thanks all for the suggestions. |
|
Back to top |
|
 |
Bill Woodger
Moderator Emeritus
Joined: 09 Mar 2011 Posts: 7309 Location: Inside the Matrix
|
|
|
|
OK. I don't see why a sequence number won't, it'll be unique.
Don't lose the link. Make sure you know and keep the original seed, forget data-redundancy and have at least a second table, maintained separately, and back-ups of the original. I've seen something similar pig-up before. If the only link is that one table, then treat it like gold. Test your recovery. If the table gets screwed, the process is screwed.
Enterprise COBOL can have 31 digits, using compiler option ARITH(EXTEND).
Separately, without ARITH(EXTEND), you can only count on 15 significant digits from a COMP-2.
Don't multiply by 10**18.
01 MULTIPLY-BY-10-TO-POWER-OF-18 PIC V9(18) COMP-3.
01 MULTIPLIED-BY-10-TO-POWER-OF-18
REDEFINES MULTIPLY-BY-10-TO-POWER-OF-18
PIC 9(18) COMP-3.
Assign your random value to MULTIPLY-BY-10-TO-POWER-OF-18, then use MULTIPLIED-BY-10-TO-POWER-OF-18. |
|
Back to top |
|
 |
steve-myers
Active Member
Joined: 30 Nov 2013 Posts: 917 Location: The Universe
|
|
|
|
Bill O'Boyle wrote: |
...
I'm sure this is not your decision, but management's instead, as many suits look at Assembler and get hives.  |
I think "suits" have two - possibly reasonable - concerns about Assembler.- Maintenance. Most competent Assembler programmers appear to 2 meters under, and the "suits" refuse to train new ones.
- Security issues. The "suits" think Assembler is an open sesame to the system. It is if the "suits" do not establish access restrictions, but they're mostly too dumb to do this. If they are smart enough to realize how dumb they are, they think the Assembler programmer, whom they must consult to establish appropriate controls, will leave back doors.
|
|
Back to top |
|
 |
dick scherrer
Moderator Emeritus

Joined: 23 Nov 2006 Posts: 19243 Location: Inside the Matrix
|
|
|
|
Hello,
If the has SAS available, suggest this be used for the random number work.
SAS does a fine job and eliminates the assembler consternation. |
|
Back to top |
|
 |
Bill O'Boyle
CICS Moderator

Joined: 14 Jan 2008 Posts: 2501 Location: Atlanta, Georgia, USA
|
|
|
|
Dick,
Did you really mean "Constipation" instead of "Consternation"?
Maybe the "Suits" need more fiber?  |
|
Back to top |
|
 |
|
|