|  | Here are the routines.  The first two perform an unsigned subtraction or
addition of a delta time value from/to an absolute value.  Useful for
figuring out "what would the time be 10 days and 4 hours from now", etc.
Had I known about the LIB$SUBx type calls, I probably would have used them.
I searched high and low through the MTH$ RTL routines and found nothing
(which was no surprise since the VAX has no integer quadword arithmetic 
instructions), so I gave up.
The last two routines are LOGICAL routines which do comparisons of absolute
times.  Use like :  IF ( DATE_LE(abs_time1, abs_time2) ) THEN
All arguments are quadword types except the result of the functions.  I use
REAL*8 to hold binary time values, I am sure that any 8 byte entity would
work (array of 8 BYTEs, array of 2 INTEGER*4, etc.).  To use, do an
EXTRACT DATE.MAR from NOTES, edit the file to get rid of the header text,
and do a MACRO DATE to produce the object.
	.TITLE	DATE_ROUTINES - Date arithmetic support routines
	.IDENT	/01.00/
	.PSECT	DATE_ROUTINES, PIC, EXE, REL, SHR, RD, NOWRT
;==============================================================================
;	S U B _ D A T E
;==============================================================================
;	General Electric Corporation
;	NORYL Products Division
;	Selkirk, N.Y.
;
;------------------------------------------------------------------------------
;	Author:	Alan M. Kozakiewicz
;	Version: 1.00
;	Date:	17-November-1986
;
;	Modification history:
;	(ECO)		(Date)		(Who)
;
;------------------------------------------------------------------------------
;	Description:
;
;		Called with CALLG instruction (AP => argument list). Performs
;	an unsigned subtraction of a delta time value from and absolute time
;	value and returns an absolute time value.  P1 = P2 - P3
;------------------------------------------------------------------------------
;	Inputs:
;------------------------------------------------------------------------------
;	Outputs:
;------------------------------------------------------------------------------
;
	.ENTRY	SUB_DATE,^M<>
;	P1 = RESULT
;	P2 = ABSOLUTE TIME
;	P3 = DELTA TIME
	MOVQ	@8(AP), @4(AP)		; Move absolute time to result
	MOVL	12(AP), R2		; R2 point to delta time
	MOVL	4(AP), R1		; R1 point to result
	MCOML	(R2), (R2)		; Change delta time to absolute
	MCOML	4(R2), 4(R2)
	SUBL	(R2), (R1)		; Subtract both halves
	SBWC	4(R2), 4(R1)
	RET
;==============================================================================
;	A D D _ D A T E
;==============================================================================
;	General Electric Corporation
;	NORYL Products Division
;	Selkirk, N.Y.
;
;------------------------------------------------------------------------------
;	Author:	Alan M. Kozakiewicz
;	Version: 1.00
;	Date:	17-November-1986
;
;	Modification history:
;	(ECO)		(Date)		(Who)
;
;------------------------------------------------------------------------------
;	Description:
;
;		Called with CALLG instruction (AP => argument list). Performs
;	an unsigned addition of a delta time value and an absolute time
;	value and returns an absolute time value.  P1 = P2 + P3
;------------------------------------------------------------------------------
;	Inputs:
;------------------------------------------------------------------------------
;	Outputs:
;------------------------------------------------------------------------------
;
	.ENTRY	ADD_DATE,^M<>
;	P1 = RESULT
;	P2 = ABSOLUTE TIME
;	P3 = DELTA TIME
	MOVQ	@8(AP), @4(AP)		; Move absolute time to result
	MOVL	12(AP), R2		; R2 point to delta time
	MOVL	4(AP), R1		; R1 point to result
	MCOML	(R2), (R2)		; Change delta time to absolute
	MCOML	4(R2), 4(R2)
	ADDL	(R2), (R1)		; Add both halves
	ADWC	4(R2), 4(R1)
	RET
;==============================================================================
;	D A T E _ L E
;==============================================================================
;	General Electric Corporation
;	NORYL Products Division
;	Selkirk, N.Y.
;
;------------------------------------------------------------------------------
;	Author:	Alan M. Kozakiewicz
;	Version: 1.00
;	Date:	18-November-1986
;
;	Modification history:
;	(ECO)		(Date)		(Who)
;
;------------------------------------------------------------------------------
;	Description:
;
;		Called with CALLG instruction (AP => argument list). Performs
;	a comparison (unsigned) of the two arguments.  Sets result (R0) to
;	TRUE if (P1 .LE. P2).
;------------------------------------------------------------------------------
;	Inputs:
;------------------------------------------------------------------------------
;	Outputs:
;------------------------------------------------------------------------------
;
	.ENTRY	DATE_LE,^M<>
	CLRL		R0			; Set to FALSE
	MOVL		4(AP), R1		; R1 => P1
	MOVL		8(AP), R2		; R2 => P2
	CMPL		4(R1), 4(R2)		; IS P1 .LE. P2 ?
	BGTRU		20$			; No way, GT
	BLSSU		10$			; Yes, LT
	CMPL		(R1), (R2)		; Check the low order if EQ
	BGTRU		20$			; GT
10$:	MOVL		#1, R0			; Set result to TRUE
20$:
	RET
;==============================================================================
;	D A T E _ G E
;==============================================================================
;	General Electric Corporation
;	NORYL Products Division
;	Selkirk, N.Y.
;
;------------------------------------------------------------------------------
;	Author:	Alan M. Kozakiewicz
;	Version: 1.00
;	Date:	18-November-1986
;
;	Modification history:
;	(ECO)		(Date)		(Who)
;
;------------------------------------------------------------------------------
;	Description:
;
;		Called with CALLG instruction (AP => argument list). Performs
;	a comparison (unsigned) of the two arguments.  Sets result (R0) to
;	TRUE if (P1 .GE. P2).
;------------------------------------------------------------------------------
;	Inputs:
;------------------------------------------------------------------------------
;	Outputs:
;------------------------------------------------------------------------------
;
	.ENTRY	DATE_GE,^M<>
	CLRL		R0			; Set to FALSE
	MOVL		4(AP), R1		; R1 => P1
	MOVL		8(AP), R2		; R2 => P2
	CMPL		4(R1), 4(R2)		; IS P1 .GE. P2 ?
	BLSSU		20$			; No way, LT
	BGTRU		10$			; Yes, GT
	CMPL		(R1), (R2)		; Check the low order if EQ
	BLSSU		20$			; LT
10$:	MOVL		#1, R0			; Set result to TRUE
20$:
	RET
	.END
 | 
|  | If I were a FORTRAN programmer (which I are, so what?), a code segment
might look like this:
	REAL*8	NOW		! Will hold todays date
	REAL*8	DELTA		! Will hold increment
	REAL*8	FUTURE		! Will hold result
	CHARACTER*27 STR
	CALL SYS$BINTIM('-- ::.',NOW)		!Get the date/time now
	CALL SYS$BINTIM('7 12:00:00.00',DELTA)	!7 Days and 12 hours into the
C						 future
	CALL ADD_DATE (FUTURE, NOW, DELTA)
	CALL SYS$ASCTIM (, STR, FUTURE, )	! Convert to ASCII
	TYPE *, STR				! Print out result
 |