Loading
Russian
Polish
Mikołaj Hajduk's Homepage

Calendar functions library

C
reation of the library containing functions for inter-calendar conversions (between Julian and Gregorian calendars) was mainly inspired by my interest to history (especially to its ancient part). In addition it was interesting challenge from the mathematical and programming points of view. First I had to create mathematical models of all calendar functions which were then implemented in FASM assembler. In the first version of this library calendar functions were limited to the time interval starting from the beginning of the common era (for the Julian calendar) and from 15 Oct 1582 (for the Gregorian calendar). Ending point was some day in the future distant 11 million years from the present day. But many dates interesting for historians is placed before beginning of the common era. Consequently, it was necessary to reconstruct mathematical models of the calendar functions and their implementations in such a way that they still could be used in the time interval of 11 million years but with the beginning of the common era placed almost exactly in the middle of this distance. Library functions were extended for dates preceding introduction of the Gregorian calendar and 1 Jan 1 CE for the Julian calendar (such calendars are named proleptic). After all these changes every date conversion between both systems is very convenient.

This library has description in three languages (English, Russian and Polish) in order to maximize the number of the potential users.

Abilities of the library functions

Functions exported from DLL library support various operations:

  • work with dates from the interval of 11 million years:
    • from 1 Jan 5843880 BCE to 3 Aug 5915100 for the Julian calendar,
    • from 30 Dec 5844001 BCE to 17 Jan 5915222 for the Gregorian calendar,
  • convenient conversions between Julian and Gregorian calendars for dates from supported time interval,
  • calculation of the day of the week for the given date,
  • calculation of the number of the day in the year,
  • determining if the given year is leap in chosen calendar,
  • calculation of the "absolute" day number for the given date (it could be used to calculation of the distance between two dates).

Short description of the calendar functions

The library contains 8 functions for operations with dates:

  • DayOfWeek - calculates the day of the week for the given date,
  • IsLeapYear - determines if the given year is leap in the chosen calendar,
  • MDToDayNum - calculates the ordinal number of the day in the year,
  • DayNumToMD - converts the ordinal number of the day in the year to the adequate month and day numbers,
  • DateToAbsDayNum - calculates the absolute day number for the given date,
  • AbsDayNumToDate - converts the absolute day number to the adequate date (for the chosen calendar),
  • GregorianToJulian - converts the Gregorian date to the adequate Julian date,
  • JulianToGregorian - converts the Julian date to the adequate Gregorian date.

Source

Content of the library source file is presented below:

; Calendar functions library written with FASM assembler.
;
; Abilities:
;	* works with dates from the interval of 11 million years:
;		- from 1 Jan 5843880 BCE to 3 Aug 5915100 for the Julian calendar,
;		- from 30 Dec 5844001 BCE to 17 Jan 5915222 for the Gregorian calendar,
;	* convenient conversions between Julian and Gregorian calendars for dates
;	  from supported time interval,
;	* calculation of the day of the week for the given date,
;	* calculation of the number of the day in the year,
;	* determining if the given year is leap in chosen calendar,
;	* calculation of the "absolute" day number for the given date (it could be
;	  used to calculation of the distance between two dates).	  
;
; (C) Mikołaj Hajduk, 16.06.2008.
;
format PE GUI 4.0 DLL
entry DllEntryPoint

include 'win32a.inc'

; Definitions of the used constants.
;
C1	= 365			; Number of days in a normal year.

C4	= 4*C1 + 1		; Number of days in the 4-year cycle (base cycle of the Julian
				; calendar).
				
C100	= 25*C4 - 1		; Number of days in a "normal" century in the Gregorian calendar
				; (i.e. century ending with a normal, 365-day, year).

C400	= 4*C100 + 1		; Number of days in the complete 400-year cycle of the Gregorian
				; calendar. 

k	= 30

J	= 194796		; The constants J and G are equal to the numbers of the complete years
G	= 194800		; of the Julian and Gregorian calendars respectively contained in the 
				; time interval given by "Great Cycle" T.


section '.data' data readable writeable

; Table containing lengths of months of a normal year (first 12 elements) and a leap year 
; (next 12 elements).
;
MonthLen	db 31,  28,  31,  30,  31,  30,  31,  31,  30,  31,  30,  31
		db 31,  29,  31,  30,  31,  30,  31,  31,  30,  31,  30,  31

; Table containing values of the function 'DaySum' for every pair (month number, leap year flag).
;
DaySum		dw  0,  31,  59,  90, 120, 151, 181, 212, 243, 273, 304, 334
		dw  0,  31,  60,  91, 121, 152, 182, 213, 244, 274, 305, 335


section '.code' code readable executable

proc	DllEntryPoint, hinstDLL, fdwReason, lpvReserved
	mov	eax, TRUE
	ret
endp

; DWORD DayOfWeek(DWORD Y, DWORD M, DWORD D, DWORD Gregorian)
;
; This function calculates the day of the week for the given date. Each day of the week is identified by number:
; 0 - Sunday, 1 - Monday, 2 - Tuesday, 3 - Wednesday, 4 - Thursday, 5 - Friday, 6 - Saturday.
;
; Parameters:
;	Y - year,
;	M - month,
;	D - day,
;	Gregorian - chosen calendar (0 - Julian, 1 - Gregorian).
;
; Returned values:
;	* 0, 1, ..., 6 if the date is valid,
;	* -1 for the invalid parameters.
;
proc	DayOfWeek, Y, M, D, Gregorian

	pushfd
	push	ebx edx

	stdcall DateToAbsDayNum, [Y], [M], [D], [Gregorian]		; eax := N
	test	eax, eax
	jz	.Error

	mov	ebx, 7							;
	xor	edx, edx						;
	add	eax, 5							; edx := (eax + 5) mod 7 = (N + 5) mod 7
	adc	edx, edx						;
	div	ebx							;

	xchg	eax, edx						; eax := edx
	jmp	.End

	.Error:
		mov	eax, -1
	.End:

	pop	edx ebx
	popfd

	ret
endp

; DWORD IsLeapYear(DWORD Y, DWORD Gregorian)
;
; This function determines if the given year is leap in the chosen calendar.
;
; Parameters:
;	Y - year,
;	Gregorian - chosen calendar (0 - Julian, 1 - Gregorian).
;
; Returned values:
;	* 1 if the year Y is leap, 0 - in opposite case,
;	* -1 for the invalid parameters.
;
proc	IsLeapYear, Y, Gregorian

	pushfd
	push	ebx edx

	.CheckParameters:
		test	[Gregorian], -2					; 0 <= Gregorian <= 1
		jnz	.Error						;

	.IsYNegative:
		mov	eax, [Y]					; eax := Y
		test	eax, eax
		jz	.Error
		jns	.CheckCalendar
									; eax < 0 (Y < 0)
									;
		inc	eax						; eax := eax + 1
		neg	eax						; eax := -eax = -(Y + 1) = -Y - 1 =
									;      = |Y| - [Y < 0] = Y'

	.CheckCalendar:
		cmp	[Gregorian], 0
		je	.mod4

	.Gregorian:
		xor	edx, edx					; eax := E(eax / 100) = E(Y' / 100)
		mov	ebx, 100					; edx := eax mod 100 = Y' mod 100
		div	ebx						; 

		test	edx, edx
		jz	.mod4

		mov	eax, edx					; eax := edx = Y' mod 100
									; 
									; {(Y' mod 100) mod 4 = Y' mod 4} 

	.mod4:
		shr	eax, 1						; eax := E(eax / 2); CF := eax mod 2
		jc	.Result						; 

		shr	eax, 1						; eax := E(eax / 2); CF := eax mod 2
		jmp	.Result						;

	.Error:
		mov	eax, -1
		jmp	.End

	.Result:
		setnc	al						; eax := not CF
		movzx	eax, al						;

	.End:

	pop	edx ebx
	popfd

	ret
endp

; DWORD MDToDayNum(DWORD M, DWORD D, DWORD LeapYearFlag)
;
; This function calculates the ordinal number of the day in the year.
;
; Parameters:
;	M - month,
;	D - day,
;	LeapYearFlag - flag determining if the year is leap (0 - normal year, 1 - leap year).
;
; Returned values:
;	* 1, 2, ..., 365 for the normal year, 1, 2, ..., 366 for the leap year,
;	* -1 for the invalid parameters.
;
proc	MDToDayNum, M, D, LeapYearFlag

	pushfd
	push	ebx edx

	.LeapYearFlag:
		test	[LeapYearFlag], -2				; 0 <= LeapYearFlag <= 1
		jnz	.Error						;

	.Month:
		cmp	[M], 1						;
		jb	.Error						; 1 <= M <= 12
		cmp	[M], 12						;
		ja	.Error						;

	.Day:
		cmp	[D], 1						; D >= 1
		jb	.Error						;

		mov	ebx, [LeapYearFlag]				; ebx := LeapYearFlag
		lea	ebx, [ebx + 2*ebx]				; ebx := 3*ebx = 3*LeapYearFlag
		shl	ebx, 2						; ebx := 4*ebx = 12*LeapYearFlag

		mov	edx, [M]					; eax := MonthLen[M - 1 + 12*LeapYearFlag]
		movzx	eax, [MonthLen - 1 + ebx + edx]			;

		cmp	[D], eax					; D <= MonthLen[M - 1 + 12*LeapYearFlag]
		ja	.Error						;

	.CalculateDayNum:
		shl	ebx, 1						; ebx := 2*ebx = 24*LeapYearFlag
		movzx	eax, [DaySum - 2 + ebx + 2*edx]			; eax := DaySum(M, LeapYearFlag)
		add	eax, [D]					; eax := eax + D = DaySum(M, LeapYearFlag) + D 
		jmp	.End

	.Error:
		mov	eax, -1

	.End:

	pop	edx ebx
	popfd

	ret
endp

; DWORD DayNumToMD(DWORD n, DWORD LeapYearFlag, DWORD* M, DWORD* D)
;
; This function converts the ordinal number of the day in the year to the adequate month and day numbers. 
; The result strongly depends on the flag determining if the year is leap.
;
; Parameters:
;	n - number of the day in the year,
;	LeapYearFlag - flag determining if the year is leap (0 - normal year, 1 - leap year),
;	M - pointer to variable where the calculated month number will be stored,
;	D - pointer to variable where the calculated day number will be stored. 
;
; Returned values:
;	* 0 for the valid parameters (n, LeapYearFlag),
;	* -1 in opposite case.
;
proc	DayNumToMD, n, LeapYearFlag, M, D

	pushfd
	push	ebx ecx edx

	.CheckParameters:
		test	[LeapYearFlag], -2				; 0 <= LeapYearFlag <= 1
		jnz	.Error

		cmp	[n], 1						; n >= 1
		jb	.Error						;

		mov	eax, 365					;
		add	eax, [LeapYearFlag]				; eax := 365 + LeapYearFlag
		cmp	[n], eax					; n <= eax
		ja	.Error						;

	.CalculateMD:
		mov	ebx, [LeapYearFlag]				; ebx := LeapYearFlag
		lea	ebx, [ebx + 2*ebx]				; ebx := 3*ebx = 3*LeapYearFlag
		shl	ebx, 3						; ebx := 8*ebx = 24*LeapYearFlag

		mov	ecx, 12						;
									;
		.Loop:							; ecx := max{i; 1 <= i <= 12, DaySum(i, LeapYearFlag) < n} = m
			movzx	edx, [DaySum - 2 + ebx + 2*ecx]		;
			cmp	[n], edx				; edx := DaySum(m, LeapYearFlag)
			ja	.LoopEnd				;
			loop	.Loop					;

		.LoopEnd:
			mov	eax, [M]				; M := ecx = m
			mov	[eax], ecx				;

			mov	ecx, [n]				; ecx := n
			sub	ecx, edx				; ecx := ecx - edx = n - DaySum(m, LeapYearFlag)

			mov	eax, [D]				; D := ecx
			mov	[eax], ecx				;

			xor	eax, eax

			jmp	.End

	.Error:
		mov	eax, -1

	.End:

	pop	edx ecx ebx
	popfd

	ret
endp

; DWORD DateToAbsDayNum(DWORD Y, DWORD M, DWORD D, DWORD Gregorian)
;
; This function calculates the absolute day number for the given date.
;
; Parameters:
;	Y - year,
;	M - month,
;	D - day,
;	Gregorian - chosen calendar (0 - Julian, 1 - Gregorian).
;
; Returned values:
;	* 1, 2, ..., 2^32-1 for the valid date in the chosen calendar,
;	* 0 for the invalid parameters.
;
proc	DateToAbsDayNum, Y, M, D, Gregorian

	pushfd
	push	ebx ecx edx

	test	[Gregorian], -2						; 0 <= Gregorian <= 1
	jnz	.Error							;

	stdcall	IsLeapYear, [Y], [Gregorian]				;
	cmp	eax, -1							; eax := IsLeapYear(Y, Gregorian)
	je	.Error							;

									; Y <> 0

	mov	ebx, eax						; ebx := eax

	stdcall	MDToDayNum, [M], [D], ebx				;
	cmp	eax, -1							; eax := MDToDayNum(M, D, ebx) = n
	je	.Error							;

	mov	ecx, [Y]						;
	cmp	ecx, 0							; ecx := Y
	jg	.CalculateDayNum					;

	inc	ecx							; Y < 0
									; ecx := ecx + 1 = Y + 1 = Y + [Y < 0]

	.CalculateDayNum:
		add	ecx, k*J					; 
		cmp	[Gregorian], 0					; ecx := ecx + kJ + k(G-J)[Gregorian = 1] =
		je	.Yprim0						;      = Y + [Y < 0] + kJ + k(G-J)[Gregorian = 1] = Y'
		add	ecx, k*(G-J)					; 

	.Yprim0:
		cmp	ecx, 0						;
		jne	.YprimPositive					; Y' = 0
		sub	eax, 364					; eax := eax - 364 = n - 364
		jmp	.End						;

	.YprimPositive:							; Y' > 0
									;
		dec	ecx						; ecx := ecx - 1 = Y' - 1
		mov	ebx, eax					; ebx := eax = n

		mov	eax, 365					; eax := 365
		mul	ecx						; eax := 365 * ecx = 365(Y' - 1)
		
		shr	ecx, 2						; ecx := E(ecx / 4) = E((Y' - 1) / 4)
		add	eax, ecx					; eax := eax + ecx = 365(Y' - 1) + E((Y' - 1) / 4)
		add	eax, ebx					; eax := eax + ebx = eax + n =
									;      = 365(Y' - 1) + E((Y' - 1) / 4) + n

		cmp	[Gregorian], 0
		jz	.End

	.Gregorian:
		push	eax						; X := eax

		xor	edx, edx					;
		mov	eax, ecx					; eax := ecx = E((Y' - 1) / 4)
		mov	ebx, 25						;
		div	ebx						; eax := E(eax / 25) = E(E((Y' - 1) / 4) / 25) =
									;      = E((Y' - 1) / 100)

		mov	ecx, eax					; ecx := eax = E((Y' - 1) / 100)
		pop	eax						; eax := X = 365(Y' - 1) + E((Y' - 1) / 4) + n

		sub	eax, ecx					; eax := eax - ecx = 365(Y' - 1) + E((Y' - 1) / 4) + n -
									;                    - E((Y' - 1) / 100)

		shr	ecx, 2						; ecx : = E(ecx / 4) = E(E((Y' - 1) / 100) / 4) =
									;       = E((Y' - 1) / 400)


		add	eax, ecx					; eax := eax + ecx = 365(Y' - 1) + E((Y' - 1) / 4) + n -
									;                    - E((Y' - 1) / 100) + E((Y' - 1) / 400)

		add	eax, 2						; eax := eax + 2 = 365(Y' - 1) + E((Y' - 1) / 4) + n -
									;                  - E((Y' - 1) / 100) + E((Y' - 1) / 400) + 2 =
									;                = N

		jmp	.End

	.Error:
		xor	eax, eax

	.End:

	pop	edx ecx ebx
	popfd

	ret
endp

; DWORD AbsDayNumToDate(DWORD N, DWORD Gregorian, DWORD* Y, DWORD* M, DWORD* D)
;
; This function converts the absolute day number N = 1, 2, ..., 2^32-1 to the adequate date (for the chosen calendar).
;
; Parameters:
;	N - absolute day number,
;	Gregorian - chosen calendar (0 - Julian, 1 - Gregorian),
;	Y - pointer to variable where the calculated year number will be stored,
;	M - pointer to variable where the calculated month number will be stored,
;	D - pointer to variable where the calculated day number will be stored.
;
; Returned values:
;	* 0 for the valid parameters (N, Gregorian),
;	* -1 in opposite case.
;
proc	AbsDayNumToDate, N, Gregorian, Y, M, D

	pushfd
	push	ebx ecx edx

	cmp	[N], 0							; N <> 0
	je	.Error							;

	test	[Gregorian], -2						; 0 <= Gregorian <= 1
	jnz	.Error							;

	xor	ecx, ecx						; ecx := 0
	
	mov	eax, [N]						; eax := N - 1
	dec	eax							;

	cmp	[Gregorian], 0
	je	.Julian

	.Gregorian:
		cmp	eax, 1
		ja	.NextDays

									; 0 <= eax <= 1 (1 <= N <= 2)

		mov	ebx, [M]					; M := 12
		mov	dword [ebx], 12					;

		add	eax, 30						; eax := eax + 30 = N - 1 + 30 = N + 29 

		mov	ebx, [D]					; D := eax = N + 29
		mov	[ebx], eax					;

		mov	ecx, -k*G - 1					; ecx := -kG - 1

		jmp	.ReturnY

	.NextDays:							; eax > 1 (N > 2)

		sub	eax, 2						; eax := eax - 2 = N - 1 - 2 = N - 3

		xor	edx, edx					;
		mov	ebx, C400					; eax := E(eax / C400) = E((N - 3) / C400)
		div	ebx						; edx := eax mod C400 = (N - 3) mod C400

		lea	eax, [eax + 4*eax]				; eax := 5*eax = 5*E((N - 3) / C400)
		lea	eax, [eax + 4*eax]				; eax := 5*eax = 5*(5*E((N - 3) / C400)) =
									;              = 25*E((N - 3) / C400)

		shl	eax, 4						; eax := 16*eax = 16*(25*E((N - 3) / C400)) =
									;               = 400*E((N - 3) / C400)

		xchg	ecx, eax					; ecx := eax = 400*E((N - 3) / C400)
									; 

		xchg	eax, edx					; eax := edx = (N - 3) mod C400
									; 

		.Centuries:						;
			cmp	eax, C100				;
			jb	.Julian					;
									;
			add	ecx, 100				;
			sub	eax, C100				;
									;
			cmp	eax, C100				; (eax, ecx) := P(eax, ecx) = 
			jb	.Julian					;             = P((N - 3) mod C400, 400*E((N - 3) / C400)) =
									;             = (N100, Y100)
			add	ecx, 100				;
			sub	eax, C100				;
									;
			cmp	eax, C100				;
			jb	.Julian					;
									;
			add	ecx, 100				;
			sub	eax, C100				;

	.Julian:
									;                             /
									;                             |  (N - 1, 0)                                 ; Gregorian = 0
									; (N100, Y100) = (eax, ecx) = <
									;                             |  P((N - 3) mod C400, 400*E((N - 3) / C400)) ; Gregorian = 1
									;                             \

		xor	edx, edx					;
		mov	ebx, C4						; eax := E(eax / C4) = E(N100 / C4)
		div	ebx						; edx := eax mod C4 = N100 mod C4

		shl	eax, 2						; eax := 4*eax = 4*E(N100 / C4)

		add	ecx, eax					; ecx := ecx + eax = Y100 + 4*E(N100 / C4)

		.Years:							;
			inc	ecx					;
			cmp	edx, C1					;
			jb	.MD					;
									;
			sub	edx, C1					;
									;
			inc	ecx					; (edx, ecx) := Q(edx, ecx) =
			cmp	edx, C1					;             = Q(N100 mod C4, Y100 + 4*E(N100 / C4)) =
			jb	.MD					;             = (N', Y*)
									;
			sub	edx, C1					;
									;
			inc	ecx					;
			cmp	edx, C1					;
			jb	.MD					;
									;
			sub	edx, C1					;
									;
			inc	ecx					;

	.MD:
		inc	edx						; edx := edx + 1 = N' + 1

		stdcall	IsLeapYear, ecx, [Gregorian]			; eax := IsLeapYear(ecx, Gregorian) =
									;      = IsLeapYear(Y*, Gregorian)

		stdcall	DayNumToMD, edx, eax, [M], [D]			; eax := DayNumToMD(edx, eax, M, D) =
									;      = DayNumToMD(N' + 1, IsLeapYear(Y*, Gregorian), M, D)

		cmp	[Gregorian], 0
		je	.JulianYears

		.GregorianYears:					;
			sub	ecx, k*(G - J)				;
									; ecx := ecx - kJ - k(G - J)[Gregorian = 1] =
		.JulianYears:						;      = Y* - kJ - k(G - J)[Gregorian = 1] = 
			sub	ecx, k*J				;      = Y'

			cmp	ecx, 0
			jg	.ReturnY
									; ecx <= 0 (Y' <= 0)

			dec	ecx					; ecx := ecx - 1 = Y' - 1 = Y' - [Y' <= 0]

		.ReturnY:
			mov	eax, [Y]				; Y := ecx
			mov	[eax], ecx				;

		xor	eax, eax
		jmp	.End

	.Error:
		mov	eax, -1

	.End:

	pop	edx ecx ebx
	popfd

	ret
endp

; DWORD GregorianToJulian(DWORD Yg, DWORD Mg, DWORD Dg, DWORD* Yj, DWORD* Mj, DWORD* Dj)
;
; This function converts the Gregorian date to the adequate Julian date.
;
; Parameters:
;	Yg - year of the Gregorian date,
;	Mg - month of the Gregorian date,
;	Dg - day of the Gregorian date,
;	Yj - pointer to variable where the calculated year number of the Julian date will be stored,
;	Mj - pointer to variable where the calculated month number of the Julian date will be stored,
;	Dj - pointer to variable where the calculated day number of the Julian date will be stored.
;
; Returned values:
;	* 0 for the valid Gregorian date,
;	* -1 in opposite case.
;
proc	GregorianToJulian, Yg, Mg, Dg, Yj, Mj, Dj

	.GregorianToNum:
		stdcall DateToAbsDayNum, [Yg], [Mg], [Dg], 1
		test	eax, eax
		jz	.Error

	.NumToJulian:
		stdcall AbsDayNumToDate, eax, 0, [Yj], [Mj], [Dj]
		jmp	.End

	.Error:
		mov	eax, -1

	.End:

	ret
endp

; DWORD JulianToGregorian(DWORD Yj, DWORD Mj, DWORD Dj, DWORD* Yg, DWORD* Mg, DWORD* Dg)
;
; This function converts the Julian date to the adequate Gregorian date.
;
; Parameters:
;	Yj - year of the Julian date,
;	Mj - month of the Julian date,
;	Dj - day of the Julian date,
;	Yg - pointer to variable where the calculated year number of the Gregorian date will be stored,
;	Mg - pointer to variable where the calculated month number of the Gregorian date will be stored,
;	Dg - pointer to variable where the calculated day number of the Gregorian date will be stored.
;
; Returned values:
;	* 0 for the valid Julian date,
;	* -1 in opposite case.
;
proc	JulianToGregorian, Yj, Mj, Dj, Yg, Mg, Dg

	.JulianToNum:
		stdcall DateToAbsDayNum, [Yj], [Mj], [Dj], 0
		test	eax, eax
		jz	.Error

	.NumToGregorian:
		stdcall AbsDayNumToDate, eax, 1, [Yg], [Mg], [Dg]
		jmp	.End

	.Error:
		mov	eax, -1

	.End:

	ret
endp


section '.edata' export data readable

	export	'Calendar.dll',\
		AbsDayNumToDate,	'AbsDayNumToDate',\
		DateToAbsDayNum,	'DateToAbsDayNum',\
		DayNumToMD,		'DayNumToMD',\
		DayOfWeek,		'DayOfWeek',\
		GregorianToJulian,	'GregorianToJulian',\
		IsLeapYear,		'IsLeapYear',\
		JulianToGregorian,	'JulianToGregorian',\
		MDToDayNum,		'MDToDayNum'


section '.reloc' fixups data discardable

© 2007-2020, Mikołaj Hajduk | Last modified: 2020-03-05 19:47:19 CET