The (MultiValue) Dating Game

No matter the application, date values typically play a crucial role. When was the order created? When did the packing slip get printed? When will the payment be due?

Fortunately, calculating dates in MultiValue Basic is really pretty easy. Start with an internal date and add or subtract a certain number of days, and output convert the result and we're there, right? While this is a great start, we can do much more with just a little more code.

Let's take a peek at some common date calculations and how we might implement them as MultiValue Basic subroutines.

Calculating the First Day of Next Month

Let's start with something simple. Knowing the current month and year, getting the start of the next month is as simple as adding 1 to the current month and getting the corresponding date. About the only complexity here is watching out for end of year; if the month goes larger than 12, we need to roll the month over to 1 and increment the year. See figure 1.

SUBROUTINE FIRST.DAY.NEXT.MONTH(NEXT.DATE,TODAY)
*
TODAY.MONTH = OCONV(TODAY,'DM')
TODAY.YEAR  = OCONV(TODAY,'D4Y')
*
NEXT.MONTH  = TODAY.MONTH + 1
NEXT.YEAR   = TODAY.YEAR
*
IF (NEXT.MONTH GT 12) THEN
  NEXT.MONTH -= 12
  NEXT.YEAR  += 1
END
*
NEXT.DATE = ICONV(NEXT.MONTH : '/01/' : NEXT.YEAR,'D')
*
RETURN

In all of our examples, the TODAY variable represents a day in a month — any day in that month — and the NEXT.DATE variable is returned with the result. The return value is listed as the first formal argument so that these subroutines can be called both from other Basic routines as well as SUBR(..) type dictionaries for those platforms that support this feature.

Note the NEXT.MONTH -= 12 when the month is greater than 12. In this example this is a little bit of overkill. But stay tuned, this will become an important detail shortly.

Calculating the Last Day of the Current Month

The last day of a month is typically considered one of the more vexing calculations, as you have to factor in the number of days in each month, leap years, and all that, right? Not at all! Unless the Mayans were right, the last day of a month is always followed by the first day of the next month, so all we have to do is calculate the first day of the next month (fig. 1) and subtract a day. See figure 2.

SUBROUTINE LAST.DAY.THIS.MONTH(NEXT.DATE,TODAY)
*
CALL FIRST.DAY.NEXT.MONTH(NEXT.DATE,TODAY)
NEXT.DATE -= 1
*
RETURN

Calculating the First Day of Any Future or Past Month

The calculation of any first day of a month — future or past — requires only minor changes to our first example. Instead of adding 1 to the month, we simply add a number of months future or past. To handle both future and past in the same routine we need to watch for the month being less than 1 or greater than 12 and adjust it accordingly, considering that we may have to count back or forward multiple years. For future years, every time we subtract 12 from the month, we add 1 to the year. For past year, every time we add 12 to the month, we subtract 1 from the year. See figure 3.

SUBROUTINE FIRST.DAY.ADJ.MONTH(NEXT.DATE,TODAY,MONTHS)
*
TODAY.MONTH = OCONV(TODAY,'DM')
TODAY.YEAR  = OCONV(TODAY,'D4Y')
*
NEXT.MONTH  = TODAY.MONTH + MONTHS
NEXT.YEAR   = TODAY.YEAR
*
BEGIN CASE
  CASE (NEXT.MONTH GT 12)
    LOOP
    WHILE (NEXT.MONTH GT 12) DO
      NEXT.MONTH -= 12
      NEXT.YEAR  += 1
    REPEAT
  CASE (NEXT.MONTH LT 1)
    LOOP
    WHILE (NEXT.MONTH LT 1) DO
      NEXT.MONTH += 12
      NEXT.YEAR  -= 1
    REPEAT
END CASE
*
NEXT.DATE = ICONV(NEXT.MONTH : '/01/' : NEXT.YEAR,'D')
*
RETURN

Calculating the Last Day of Any Future or Past Month

With what we've created so far, calculating the last day of any future or past month is easy. We simply calculate the first day of the month following the month requested and subtract one day. Also note that by adding 1 to the MONTHS variable in the subroutine argument, the MONTHS variable will remain unchanged when this routine returns to its caller. See figure 4.

SUBROUTINE LAST.DAY.ADJ.MONTH(NEXT.DATE,TODAY,MONTHS)
*
CALL FIRST.DAY.ADJ.MONTH(NEXT.DATE,TODAY,MONTHS + 1)
*
NEXT.DATE -= 1
*
RETURN

Calculating the First Tuesday in a Month

Now that we know how to calculate the first day in a month, it might be useful to be able to calculate the first Tuesday (or any day of week for that matter). Once we know the first Tuesday, we can easily calculate the second and subsequent by adding in 7 (days) for each week.

At first blush this seems like this could get quite complicated. Au contraire! We simply need to figure out the first day of the month (figure 3), back up to the last Sunday, and then add in the value for the day of week we want. Finally, if the final day is before the beginning of the month, we simply add 7 days to push our result into the current month. See figure 5.

SUBROUTINE FIRST.MONTH.DOW(NEXT.DATE,TODAY,DOW)
*
FIRST = ''
CALL FIRST.DAY.ADJ.MONTH(FIRST,TODAY,0)
FIRST.DOW   = OCONV(FIRST,'DW')
IF (FIRST.DOW EQ 0) THEN
  FIRST.DOW = 7
END
*
NEXT.DATE = FIRST - FIRST.DOW + DOW
IF (FIRST.DOW GT DOW) THEN
  NEXT.DATE += 7
END
*
RETURN

There is one UniData quirk that may not exist in other platforms: Sunday could be represented as 0 or 7, depending on how an option is set. Therefore, we have a couple lines in here to change the day of week to 7 if the "DW" (day of week) conversion returns 0.

Calculating the Last Tuesday in a Month

Calculating the last Tuesday in the month is effectively identical to the earlier example, except that we start from the last day of the month, back up to Sunday, add in the day of week we want, and if it's beyond the end of the month we subtract 7 to pull the result into the correct month. See figure 6.

SUBROUTINE LAST.MONTH.DOW(NEXT.DATE,TODAY,DOW)
*
LAST = ''
CALL LAST.DAY.ADJ.MONTH(LAST,TODAY,0)
LAST.DOW   = OCONV(LAST,'DW')
IF (LAST.DOW EQ 0) THEN
  LAST.DOW = 7
END
*
NEXT.DATE = LAST - LAST.DOW + DOW
IF (LAST.DOW LT DOW) THEN
  NEXT.DATE -= 7
END
*
RETURN

Calculating a Week Number

Being able to calculate a week number can be a very useful thing, especially for financial and metric reporting. However, this calculation is often victim of interpretation. For example, what exactly constitutes a "week"? Is it Sunday through Saturday? Wednesday through Tuesday? Or does the first day of the week depend on the day of week of the first day of the year?

When the first day of the week is based on the first day of the year, calculating a week number is simple; subtract the current date from the day before the first day of the year, divide by 7, take the integer result, and add 1 if there's any remainder from the division. Though the calculation is simple, it suffers under the problem that in a Monday through Friday work week some days could be assigned one week number, whereas other days in that same work week might be assigned a different number.

To try to keep Monday through Friday together, let's calculate the week number based on Sunday to Saturday. We start by calculating January 1 of the current year, and then back it up to Sunday, understanding that the Sunday may actually be in the prior year. Subtracting today from that Sunday tells us how many days have elapsed, and dividing this by 7 and taking the integer result tells us the number of weeks. Well, almost. If there is any remainder left over from the division, or if the week number is 0 (as it would be when January 1 st falls on a Sunday), we add 1 to the result. See figure 7.

SUBROUTINE WEEK.NUMBER(WEEK,TODAY)
*
TODAY.YEAR = OCONV(TODAY,'D4Y')
JAN.1      = ICONV('1/1/' : TODAY.YEAR,'D')
JAN.1.DOW  = OCONV(JAN.1,'DW')
IF (JAN.1.DOW EQ 0) THEN
  JAN.1.DOW = 7
END
*
IF (JAN.1.DOW EQ 7) THEN
  SUNDAY = JAN.1
END ELSE
  SUNDAY = JAN.1 - JAN.1.DOW
END
*
WEEK = INT((TODAY - SUNDAY) / 7)
IF (MOD(TODAY,SUNDAY) GT 0) OR (WEEK EQ 0) THEN
  WEEK += 1
END
*
RETURN

Calculating This Day in a Future or Past Month

Interestingly, this is one of the more complex date calculations. In short, while the 15 th is valid in every month, the 31 st is not. In this latter case we need to roll the 31 st back to the 30 th , or 28 th , or even the 29 th every leap year. Fortunately, we don't have to worry too much about all those details. As this only happens at the end of a month, we can attempt to calculate a date for a given month, day, and year, and if it's not valid, we can decrement the day number and try again until we get a valid date. See figure 8.

SUBROUTINE THIS.DAY.NEXT(NEXT.DATE,TODAY,MONTHS)
*
TODAY.MONTH = OCONV(TODAY,'DM')
TODAY.DAY = OCONV(TODAY,'DD')
TODAY.YEAR = OCONV(TODAY,'D4Y')
*
NEXT.MONTH = TODAY.MONTH + MONTHS
NEXT.YEAR = TODAY.YEAR
*
BEGIN CASE
CASE (NEXT.MONTH GT 12)
LOOP
WHILE (NEXT.MONTH GT 12) DO
NEXT.MONTH -= 12
NEXT.YEAR += 1
REPEAT
CASE (NEXT.MONTH LT 1)
LOOP
WHILE (NEXT.MONTH LT 1) DO
NEXT.MONTH += 12
NEXT.YEAR -= 1
REPEAT
END CASE
*
LOOP
NEXT.DATE = ICONV(NEXT.MONTH : '/' : TODAY.DAY : '/' : NEXT.YEAR,'D')
WHILE (NEXT.DATE EQ '') DO
TODAY.DAY -= 1
REPEAT
*
RETURN

Determining U.S. vs. International Date

In all of the examples so far I've assumed that the dates will be formatted as month/day/year, as they are here in the U.S. Certainly it would be no big deal for our non-American friends to translate these routines into the day/month/year format used by much of the rest of the world. But what if you're writing an application that needs to support both U.S. and International date formats?

Most MultiValue systems have some system variable that will tell whether the system is configured for U.S. or International dates. While I appreciate that such a feature is available, I've never quite grown to trust it, especially not for application portability. Besides, making this determination in code is really quite simple.

If we try to calculate a known date in U.S. format and the ICONV(..) returns nothing, we can have some confidence that the international date format is enabled. Nothing more complicated is needed. See Figure 9.

SUBROUTINE DATE.FORMAT(ANS)
*
IF (ICONV('02/28','D') EQ '') THEN
  ANS = 'I'
END ELSE
  ANS = 'A'
END
*
RETURN

In Summary

Calculating dates is an important feature for just about every application. And compared to working in other languages, MultiValue databases make date calculations easy. Certainly there are other more involved calculations but hopefully this has shown that the whole process doesn't have to be all too complicated.

Precision Solutions

Located in LONGMONT CO.

View more articles

Featured:

Jan/Feb 2013

menu
menu