IBM Mainframe Forum Index
 
Log In
 
IBM Mainframe Forum Index Mainframe: Search IBM Mainframe Forum: FAQ Register
 

Day of the week - Is there any function in COBOL


IBM Mainframe Forums -> COBOL Programming
Post new topic   Reply to topic
View previous topic :: View next topic  
Author Message
pjnithin

Active User


Joined: 22 Dec 2005
Posts: 116

PostPosted: Thu Mar 02, 2006 3:09 am
Reply with quote

Is there any function in COBOL which day of the week is a particular date.I have a date like 2006-01-01, I want to know which day of the week is this date.
Back to top
View user's profile Send private message
maheshkg

New User


Joined: 23 Feb 2006
Posts: 3

PostPosted: Fri Mar 03, 2006 3:09 am
Reply with quote

Use
ACCEPT <variable name> FROM DAY-OF-WEEK

This returns the day.
If it is monday then it returns 1
If tuesday then 2
and so on
Back to top
View user's profile Send private message
KS

New User


Joined: 28 Feb 2006
Posts: 91
Location: Chennai

PostPosted: Fri Mar 03, 2006 11:39 am
Reply with quote

Ye he s right !
You can use DAY OF WEEK .
It return values (1 to 7) where 1 - monday,2 - Tuesday .....7 - Sunday

You can then display using an EVALUATE st.
Back to top
View user's profile Send private message
DavidatK

Active Member


Joined: 22 Nov 2005
Posts: 700
Location: Troy, Michigan USA

PostPosted: Mon Mar 06, 2006 7:32 pm
Reply with quote

pjnithin,

I don?t know of any intrinsic function that will give you the day of the week for any date. The ACCEPT .. DAY-OF-WEEK will give you the day of the week only for the current date. You cannot supply a date to the function.

Dave
Back to top
View user's profile Send private message
manyone

New User


Joined: 09 Mar 2006
Posts: 9

PostPosted: Thu Mar 09, 2006 6:09 am
Reply with quote

here's some code that will do it (note: 0=sunday)
01 filler.
03 ws-dow-str pic x(21) value 'sunmontuewedthufrisat'.
03 ws-db2-date pic x(10).
PROCEDURE DIVISION.
move '2006-03-26' to ws-db2-date
compute tally =
function mod (
function integer-of-date (
function integer(
function numval (ws-db2-date(1:4))
) * 10000
+ function integer (
function numval (ws-db2-date(6:2))
) * 100
+ function integer (
function numval (ws-db2-date(9:2))
)
), 7 )
display tally ' ' ws-dow-str ( 3 * tally + 1 : 3)
goback
Back to top
View user's profile Send private message
mmwife

Super Moderator


Joined: 30 May 2003
Posts: 1592

PostPosted: Sun Mar 12, 2006 11:10 pm
Reply with quote

Hi pjnithin,

You've been silent since your original ques, but anyway, here's another possible way to solve your problem:

P.S. It would be helpful (not to mention thoughtful) of you to communicate to the forum members how these suggestions worked for you.
Code:

DIVIDE FUNCTION INTEGER-OF-DATE(your-date) BY 7
GIVING some-fld REMAINDER your-rem
EVALUATE your-rem
    WHEN 0 DISPLAY 'SUN'
    WHEN 1 DISPLAY 'MON'
    WHEN 2 DISPLAY 'TUE'
    WHEN 3 DISPLAY 'WED'
    WHEN 4 DISPLAY 'THU'
    WHEN 5 DISPLAY 'FRI'
    WHEN 6 DISPLAY 'SAT'
END-EVALUATE


In English, the FUNC provides the # of days between your-dt and 1/1/1601 (I think that's the date). If you divide that by 7 the remainder is the # of days between your-dt's DOW and 1/1/1601's DOW. I also think the 1601 DOW is a Sunday, hence a zero remainder makes your-dt a SUDAY too.

If I'm wrong just adjust your code accordingly.

HTH
Back to top
View user's profile Send private message
martin9

Active User


Joined: 01 Mar 2006
Posts: 290
Location: Basel, Switzerland

PostPosted: Mon Mar 13, 2006 3:01 pm
Reply with quote

hy,

the le conform cobol compilers accept so called intrinsic functions,
as decribed before by mmwife.
just look there for teh synatx, there are much more
functions that are quite useful.

martin9
Back to top
View user's profile Send private message
riyasabdulla

New User


Joined: 03 Mar 2005
Posts: 1

PostPosted: Tue Mar 28, 2006 4:51 pm
Reply with quote

IS THERE ANY FUNCTION TO GET THE DAY OF WEEK FROM A DATE IN ORDINARY COBOL?
Back to top
View user's profile Send private message
manyone

New User


Joined: 09 Mar 2006
Posts: 9

PostPosted: Wed Mar 29, 2006 12:34 am
Reply with quote

here's some working code (you supply the fd)
Code:

001800 01  INPDATE-RECORD.
001900     05  INPD-YEAR          PIC 9(04).
002000     05  FILLER             PIC X(01).
002100     05  INPD-MONTH         PIC 9(02).
002200     05  FILLER             PIC X(01).
002300     05  INPD-DAY           PIC 9(02).
002400     05  FILLER             PIC X(70).
002500*
002600 WORKING-STORAGE SECTION.
002700 01  FILLER           PIC X(01) VALUE 'N'.
002800   88  NO-MORE-INPDATE          VALUE 'Y'.
002900 01  WMS-DAYNAME-DEF.
003000   03  FILLER PIC X(03) VALUE 'SUN'.
003100   03  FILLER PIC X(03) VALUE 'MON'.
003200   03  FILLER PIC X(03) VALUE 'TUE'.
003300   03  FILLER PIC X(03) VALUE 'WED'.
003400   03  FILLER PIC X(03) VALUE 'THU'.
003500   03  FILLER PIC X(03) VALUE 'FRI'.
003600   03  FILLER PIC X(03) VALUE 'SAT'.
003700 01  WMS-DAYNAME-TABLE REDEFINES WMS-DAYNAME-DEF.
003800   03  WMS-DAYNAME      PIC X(03) OCCURS 7 TIMES.
003900 01  WMS-WORK-AREA.
004000   03  WMS-YEAR       PIC 9(04).
004100   03  WMS-MONTH      PIC 9(02).
004200   03  WMS-T1         PIC 9(02).
004300   03  WMS-T4         PIC 9(04).
004400   03  WMS-T100       PIC 9(02).
004500   03  WMS-T400       PIC 9(02).
004600   03  WMS-SUM        PIC 9(04).
004700   03  WMS-WORK       PIC 9(04).
004800   03  WMS-CSYS       PIC 9(01) VALUE 1.
004900* -- DOW (1=SUNDAY)
005000   03  WMS-DOW        PIC 9(01).
005100 PROCEDURE DIVISION.
005200     OPEN INPUT INPDATE-FILE
005300     READ INPDATE-FILE
005400     AT END
005500         SET NO-MORE-INPDATE TO TRUE
005600     END-READ
005700     PERFORM
005900     UNTIL NO-MORE-INPDATE
006000         PERFORM 1010-CONVERT-DATE-TO-DOW
006100         DISPLAY INPD-YEAR '-' INPD-MONTH '-' INP-DAY
006400          ' IS ' WMS-DAYNAME ( WMS-DOW ) ', DOW=' WMS-DOW
006600         READ INPDATE-FILE
006700         AT END
006800             SET NO-MORE-INPDATE TO TRUE
006900         END-READ
007000     END-PERFORM
007100     CLOSE INPDATE-FILE
007200     GOBACK
007300     .
007400 1010-CONVERT-DATE-TO-DOW.
007500     IF INPD-MONTH < 3
007600         COMPUTE WMS-MONTH = INPD-MONTH + 12
007700         COMPUTE WMS-YEAR  = INPD-YEAR - 1
007800     ELSE
007900         COMPUTE WMS-MONTH = INPD-MONTH
008000         COMPUTE WMS-YEAR  = INPD-YEAR
008100     END-IF
008200     COMPUTE WMS-T1   = 6 * ( WMS-MONTH + 1 ) / 10
008300     COMPUTE WMS-T4   = WMS-YEAR / 4
008400     COMPUTE WMS-T100 = WMS-YEAR / 100
008500     COMPUTE WMS-T400 = WMS-YEAR / 400
008600     COMPUTE WMS-SUM  = INPD-DAY + 2 * WMS-MONTH + WMS-YEAR
008700                      + WMS-T1 + WMS-T4 - WMS-T100 + WMS-T400
008800                      + WMS-CSYS
008900     COMPUTE WMS-WORK = WMS-SUM / 7
009000*  -- DOW (1=SUNDAY)
009100     COMPUTE WMS-DOW  = WMS-SUM - 7 * WMS-WORK + 1
009200     .
Back to top
View user's profile Send private message
View previous topic :: :: View next topic  
Post new topic   Reply to topic View Bookmarks
All times are GMT + 6 Hours
Forum Index -> COBOL Programming

 


Similar Topics
Topic Forum Replies
No new posts Replace each space in cobol string wi... COBOL Programming 3
No new posts COBOL -Linkage Section-Case Sensitive COBOL Programming 1
No new posts COBOL ZOS Web Enablement Toolkit HTTP... COBOL Programming 0
No new posts Calling DFSORT from Cobol, using OUTF... DFSORT/ICETOOL 5
No new posts Generate random number from range of ... COBOL Programming 3
Search our Forums:

Back to Top