MVSFORUMS.com Forum Index MVSFORUMS.com
A Community of and for MVS Professionals
 
 FAQFAQ   SearchSearch   Quick Manuals   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

Rexx and local time displacement from GMT

 
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> TSO and ISPF
View previous topic :: View next topic  
Author Message
rgb
Beginner


Joined: 25 Nov 2003
Posts: 6
Topics: 2

PostPosted: Tue Nov 25, 2003 10:22 am    Post subject: Rexx and local time displacement from GMT Reply with quote

Anybody knows of a way to get the local time displacement from GMT in a TSO/REXX running under ISPF ?
It seems that all time function in rexx only report local time and I need to get GMT Time.

Thanks in advance for any answer...
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12378
Topics: 75
Location: San Jose

PostPosted: Tue Nov 25, 2003 10:59 am    Post subject: Reply with quote

RGb,

You can check the timezone parameter in the member CLOCKXX in SYS1.PARMLIB. If your shop has set up the GMT and local to the same time in which the offset in CLOCKXX will be 0 then you need to call a routine written in a programming language(cobol Assembler...) to get the offset from GMT.

You can code a small cobol program to just display the date. In Enterprise cobol the current data function returns a 21-character alphanumeric value that represents the calendar date, time of day, and time differential from Greenwich Mean Time provided by the system on which the function is evaluated.

Code:

IDENTIFICATION DIVISION.                               
PROGRAM-ID.    SAMPLE                                 
DATE-COMPILED.                                         
ENVIRONMENT DIVISION.                                 
CONFIGURATION SECTION.                                 
INPUT-OUTPUT SECTION.                                 
FILE-CONTROL.                                         
DATA DIVISION.                                         
                                                       
FILE SECTION.                                         
                                                       
WORKING-STORAGE SECTION.                               
                                                       
01  W-CURR-DATE              PIC X(21).               
                                                       
PROCEDURE DIVISION.                                   
                                                       
     MOVE FUNCTION CURRENT-DATE      TO W-CURR-DATE.   
                                                       
     DISPLAY 'THE DATE IS             :' W-CURR-DATE. 
                                                       
     GOBACK.                                           
                                                       


You can call this routine from rexx and get the offset.This does not consider the day light savings time.

Hope this helps...

cheers

kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
rgb
Beginner


Joined: 25 Nov 2003
Posts: 6
Topics: 2

PostPosted: Tue Nov 25, 2003 11:19 am    Post subject: Reply with quote

kolusu Thank you for you promt answer. Unfortunately the CLOCKxx in our shop contains just ETRMODE YES, ETRZONE YES, no timezone stmnt. I will try with the cobol program...
_________________
RGB
Back to top
View user's profile Send private message
Mike Chantrey
Intermediate


Joined: 10 Sep 2003
Posts: 234
Topics: 1
Location: Wansford

PostPosted: Tue Nov 25, 2003 11:43 am    Post subject: Reply with quote

If you use Language Environment (as everyone has supposed to for many years!) then the routine CEEGMTO returns the current offset from GMT. It's documented in the 'Language Environment Callable Services' manual if I remember correctly, and here is some code:
Code:

       IDENTIFICATION DIVISION.                                       
       PROGRAM-ID. MIKETMPC.                                         
      *****************************************************************
      * TEST 'CEEGMTO' LANGUAGE ENVIRONMENT GMT OFFSETROUTINE       *
****************************************************************
       DATA DIVISION.                                                 
       WORKING-STORAGE SECTION.                                       
       01  HOURS                   PIC S9(9) BINARY.                 
       01  MINUTES                 PIC S9(9) BINARY.                 
       01  SECONDS COMP-2.                                           
       01  FC.                                                       
           02  CONDITION-TOKEN-VALUE.                                 
               03  CASE-1-CONDITION-ID.                               
                   04  Severity    PIC S9(4) BINARY.                 
                   04  MSG-NO      PIC S9(4) BINARY.                 
               03  CASE-2-CONDITION-ID                               
                         REDEFINES CASE-1-CONDITION-ID.               
                   04  CLASS-CODE  PIC S9(4) BINARY.                 
                  04  CAUSE-CODE  PIC S9(4) BINARY.                 
              03  CASE-SEV-CTL    PIC X.                             
              03  FACILITY-ID     PIC XXX.                           
          02  I-S-INFO            PIC S9(9) BINARY.                 
      01  GMT-RTN   PIC X(8) VALUE 'CEEGMTO'.                       
      01  DISP-OFFSET.                                               
          03  HOURS-DISP  PIC S9(9) SIGN IS LEADING SEPARATE.       
          03  FILLER PIC X VALUE ':'.                               
          03  MINUTES-DISP  PIC S9(9) SIGN IS LEADING SEPARATE.     
          03  FILLER PIC X VALUE '/'.                               
          03  SECONDS-DISP  PIC S9(9) SIGN IS LEADING SEPARATE.     
          03  FILLER PIC X VALUE '/'.                               
      01  DISP-ERROR.                                               
          03  FILLER PIC X(28) VALUE 'CALL TO GMTO FAILED, MSGNO= '.
          03  MSG-NO-DISP PIC S9(4) SIGN IS LEADING SEPARATE.       
                                                                     
      PROCEDURE DIVISION.                                           
      A000-CONTROL.                                                 
          CALL GMT-RTN USING HOURS , MINUTES ,                       
              SECONDS , FC.                                         
                                                                       
           IF CONDITION-TOKEN-VALUE = LOW-VALUES THEN                 
               MOVE HOURS TO HOURS-DISP                               
               MOVE MINUTES TO MINUTES-DISP                           
               MOVE SECONDS TO SECONDS-DISP                           
               EXEC CICS SEND TEXT FROM(DISP-OFFSET)                   
                   FREEKB                                             
               END-EXEC                                               
           ELSE
               MOVE MSG-NO TO MSG-NO-DISP                                                       
               EXEC CICS SEND TEXT FROM(DISP-ERROR)                   
                   FREEKB                                             
               END-EXEC                                               
           END-IF.                                                     
           EXEC CICS RETURN END-EXEC.                                 
                                                                       
           GOBACK.                                                     

The above code is for CICS but easily changed to use batch displays.
If you have the LE environment, it works in COBOL II as well as LE versions of COBOL (might even work in OS/VS COBOL with LE runtimes).
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12378
Topics: 75
Location: San Jose

PostPosted: Tue Nov 25, 2003 1:20 pm    Post subject: Reply with quote

RGB,

Check this link for detailed explanation of CEEGMTO(Get offset from Greenwich Mean Time to local time) with examples.

http://publibz.boulder.ibm.com/cgi-bin/bookmgr_OS390/BOOKS/CEEA3130/3.5.35?DT=20020625092930

Hope this helps...

cheers

kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
rgb
Beginner


Joined: 25 Nov 2003
Posts: 6
Topics: 2

PostPosted: Tue Nov 25, 2003 2:32 pm    Post subject: Reply with quote

Many thanks. It works.
The cobol program is now:
Code:

...
WORKING-STORAGE SECTION.
01 HWORK PIC S9(9) USAGE IS BINARY.
01 MWORK PIC S9(9) USAGE IS BINARY.
01 SWORK PIC X(8).
01 FCWORK PIC X(12).
LINKAGE SECTION.
01 PARAMETERS.
 05 HDISP PIC +99 USAGE DISPLAY.
 05 MDISP PIC 99 USAGE DISPLAY.
PROCEDURE DIVISION USING PARAMETERS.
CALL "CEEGMTO" USING HWORK MWORK SWORK FCWORK.
MOVE HWORK TO HDISP.
MOVE MWORK TO MDISP.
GOBACK.


Now i can call COBGMTO from a TSO/REXX in this way:

Code:

/* REXX */
hwork=copies("00"x,5)
address linkpgm "cobgmto hwork"
say hwork


and it correctly displays the local time offset from GMT.
_________________
RGB
Back to top
View user's profile Send private message
kolusu
Site Admin
Site Admin


Joined: 26 Nov 2002
Posts: 12378
Topics: 75
Location: San Jose

PostPosted: Tue Nov 25, 2003 3:32 pm    Post subject: Reply with quote

Rgb,

Thanks for the feedback

Kolusu
_________________
Kolusu
www.linkedin.com/in/kolusu
Back to top
View user's profile Send private message Send e-mail Visit poster's website
Display posts from previous:   
Post new topic   Reply to topic   printer-friendly view    MVSFORUMS.com Forum Index -> TSO and ISPF All times are GMT - 5 Hours
Page 1 of 1

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


MVSFORUMS
Powered by phpBB © 2001, 2005 phpBB Group