Operating System - OpenVMS
1752794 Members
5880 Online
108789 Solutions
New Discussion юеВ

Re: COBOL / OpenVMS Override System Date

 
SOLVED
Go to solution
John T. Farmer
Regular Advisor

COBOL / OpenVMS Override System Date

Does anyone know of a way to override the system date in OpenVMS, for a COBOL application. I am modifiying/testing a series of old COBOL programs that are driven by system date (ACCEPT SYSTEM-DATE FROM DATE). For user-acceptance testing purposes, I need to "advance" they system several days at a time, running these programs. So not to affect other developers and projects, I wanted to avoid changing the actual VMS system date. Any utility or method to "ghost" a fake system date. Too numerous changes required to remove system date from the code.

No idea will be too far out for consideration.

Thanks,

John Farmer
john dot farmer at genworth dot com
11 REPLIES 11
Hein van den Heuvel
Honored Contributor
Solution

Re: COBOL / OpenVMS Override System Date

I'm sure folks have solved this many times over some 10 years back fro Y2K !

If you compile a cobol program with ACCEPT FROM DATE with /LIST/MACHINE you'll see it call DCOB$ACC_DATE.

So you can just write your own routine with that entry point, in the language of your choice, and link it with the program.
The routine can return a data from a symbol or logical, or can calculate a date based ona symbol combined with the current time.

To do this properly you might check out John Gilling's FAKE_RTL method.
Or you can just accept the "%LINK-W-MULDEF, symbol DCOB$ACC_DATE multiply defined"

For example:

$type test.cob
IDENTIFICATION DIVISION.
PROGRAM-ID. HEIN.
DATA DIVISION.
WORKING-STORAGE SECTION.
01 my-date PIC 9(6).

PROCEDURE DIVISION.
MAIN-CONTROL SECTION.
BEGIN-HERE.
ACCEPT my-date FROM DATE
DISPLAY my-date.
STOP RUN.
$cobol test
$link test,my_dcob_acc_date
%LINK-W-MULDEF, symbol DCOB$ACC_DATE multiply defined
in module DEC$COBRTL file SYS$COMMON:[SYSLIB]DEC$COBRTL.EXE;1

$ MY_DATE_OFFSET=1
$ run test
090423
$ MY_DATE_OFFSET=10
$ run test
090502

Of course you may also need:

cob_acc_date - YYMMDD
cob_acc_date_yyyy - YYYYMMDD
cob_acc_time - HHMMSSNN
cob_acc_day - YYDDD
cob_acc_day_yyyy - YYYYDDD
cob_acc_day_week - day of week as 1 - 7

Sample implementation below.
Hth,

Hein.


$type my_dcob_acc_date.c
#include
#include

void DCOB$ACC_DATE(char *yymmdd) {

void sys$gettim(), sys$numtim();
short int timbuf[7];
long long bintim, days_in_clunks;
char *symbol;

sys$gettim(&bintim);

if (symbol = getenv("MY_DATE_OFFSET")) {
days_in_clunks = atoi(symbol);
days_in_clunks *= 86400; // Second
days_in_clunks *= 10000000; // CLunks
bintim += days_in_clunks;
}
sys$numtim(timbuf,&bintim);
sprintf ( yymmdd, "%02d%02d%02d", timbuf[0] % 100, timbuf[1], timbuf[2]);
}




Wim Van den Wyngaert
Honored Contributor

Re: COBOL / OpenVMS Override System Date

Hoff
Honored Contributor

Re: COBOL / OpenVMS Override System Date

ITRC blew the post. Checked to see if this was posted before reposting. Apologies for any duplicates.


This is one of the questions that was common a decade ago; a Y2K-like question.

There's no good way to do this date-spoofing on OpenVMS, as there's no single date API for all of the stuff that can get together tangled here; the user UIs are one part of this (and easier), but there's also the kernel-mode interfaces for drivers, and stuff that gets embedded down inside tools and libraries and file systems. The user APIs are fairly well covered by simulators or by intercepts, the latter is tougher.

The Datesim stuff is one of the few Y2K packages around that covered most of (all of?) the UIs.

Other than a package that tries to catch dates or changing your own code to catch dates, changing the system date on a box you "care about" can be problematic.

You can snag the date values via the API, but it's the rest of the stack (dates on files, records, date skews in CMS libraries, etc) that gets "interesting."

The old Y2K data and such is still online:

http://h71000.www7.hp.com/openvms/products/year-2000/index.html

The way usually preferred is off-line testing.

The prices on used rx2600 and Alpha boxes are such that it's tough not to have one around. (The base boxes have been available for US$200, add a disk and a DVD, an OpenVMS FOE license and the compiler(s), and you're off and running.) Alternatively, one of the servers gets shut down, and scratch disks are used for testing.

This off-line testing also has the advantage of not risking the production databases.
John Gillings
Honored Contributor

Re: COBOL / OpenVMS Override System Date

John,

Yes it can be done, and fairly easily.

As Hein suggests, you can do it with my FAKE_RTL. Indeed it was exactly this problem (offsetting COBOL system date) that resulted in my first fake RTL, back in the late 1980's.

Create a fake rtl for DEC$COBRTL, then insert your own code for the date related routines. I used a logical name to specify a time offset, which was added to the current system time.
A crucible of informative mistakes
John T. Farmer
Regular Advisor

Re: COBOL / OpenVMS Override System Date

The vendor contacted me about DATESIM. Price was out of the ballpark for me. I only needed a very small part of the functionality it provides.

Instead, I'll have a look at FAKE_RTL and have currently coded the two accept date routines to read a logical. Those are statically linked into my programs for now.

So I'm obviously more of a business-app than a systems guy. Is the benefit of the RTL approach that it is dynamically linked (i.e., run-time-library)?

Thanks,

John
Hoff
Honored Contributor

Re: COBOL / OpenVMS Override System Date

Well, the other respondents to the contrary, this sort of thing won't work in the general case.

Capturing and skewing the time is big and very hairy problem, particularly when you're dealing with as many different spots as time gets stored. There are the file creation and modification and revision dates, there are the dates associated with CMS libraries, application dates get stored all over the place.

If you need to test this stuff, either retrofit your requirements into your COBOL code, or use a test system. (Sure, you can try fake VM. Given you have the COBOL code and you're making changes, well, what's the point? Change the code to do what you need; retrofit testing support while you're fixing the code.)

And if you can't perturb a production cluster (and as is often the case when OpenVMS is involved), then you need a test configuration. COBOL applications under test have a habit of using files, and these same COBOL applications and files are often used in production. Collisions with application testing and with active production files can be bad.

For regression testing purposes, DEC Test Manager (DTM) has date-masking capabilities; where the application runs as normal, and where DTM detects and performs text substitutions on the displayed dates.
John Gillings
Honored Contributor

Re: COBOL / OpenVMS Override System Date

John,

> Is the benefit of the RTL approach that
>it is dynamically linked (i.e., run-time-
>library)?

Exactly. With a FAKE_RTL version of DEC$COBRTL, you can define logical names for the RTLs and your time offset, and make any COBOL program run with your offset, without having to recompile or relink. Using different logical name tables, you can affect process, job, group or whole system.

However, as Hoff has pointed out, it's not necessarily going to work for everything. For example, dates in file headers will still follow the system time, so if your code is (say) checking revision dates of files, it will get confused.
A crucible of informative mistakes
John T. Farmer
Regular Advisor

Re: COBOL / OpenVMS Override System Date

Then I think this will work well for me. My apps are only concerned about data content, i.e., date columns in RMS files. Fortunately, nothing to do with the attributes of the files themselves. This dynamic linking to the RTL will solve most of my challenges concerning dates on my user-testing machine.

Will test this on my lab Alpha before introducing to the user test box.

Thanks you all VERY much!!!

John
Wim Van den Wyngaert
Honored Contributor

Re: COBOL / OpenVMS Override System Date

If you only need it once then the trial-free-for-a-month datesim can be used. I tested it and it works fine.

fwiw

Wim
Wim