source: IOIPSL/trunk/example/testcalendar.f90 @ 30

Last change on this file since 30 was 16, checked in by bellier, 17 years ago

JB: add Id (ommited !)

  • Property svn:keywords set to Id
File size: 2.0 KB
Line 
1PROGRAM testcalendar
2!-
3!$Id$
4!---------------------------------------------------------------------
5!- This program will do some basic tests on the calendar
6!---------------------------------------------------------------------
7  USE calendar
8!-
9  IMPLICIT NONE
10!-
11  REAL :: julian, sec
12  INTEGER :: year, month, day
13  INTEGER :: iread, iret
14  CHARACTER(LEN=20) :: tmp
15!-
16  INTEGER :: iargc, getarg
17  EXTERNAL iargc, getarg
18!---------------------------------------------------------------------
19!-
20! Get the command line arguments
21!-
22  iread = iargc()
23  IF (iread .EQ. 0) THEN
24    WRITE(*,*) 'Using the default calendar'
25  ELSE
26    iret = getarg(1,tmp)
27    WRITE(*,*) 'Using the calendar named :',TRIM(tmp)
28    CALL ioconf_calendar (TRIM(tmp))
29  ENDIF
30!-
31! Get the origine of the julian days
32!-
33  julian = 0.0
34  CALL ju2ymds (julian, year, month, day, sec)
35  WRITE(*,*) 'Day at which the julian day was zero :'
36  WRITE(*,*) 'Year : ',year,' Month : ',month,' Day : ',day
37!-
38! Do we get the same day back when we go back and forth
39!-
40  year = 1997
41  month = 8
42  day = 21
43  sec = 0.0
44  WRITE(*,*) 'Day transformed into julian :'
45  WRITE(*,*) 'Year : ',year,' Month : ',month,' Day : ',day
46  CALL ymds2ju (year, month, day, sec, julian)
47  WRITE(*,*) ' --> The resulting julian day : ',julian
48  CALL ju2ymds (julian, year, month, day, sec)
49  WRITE(*,*) 'The day which comes out again :'
50  WRITE(*,*) 'Year : ',year,' Month : ',month,' Day : ',day
51!-
52! Yet another test but this time with a strange dat !
53!-
54  year = 1997
55  month = 3
56  day = 34
57  sec = 0.0
58  WRITE(*,*) 'Strange day transformed into julian :'
59  WRITE(*,*) 'Year : ',year,' Month : ',month,' Day : ',day
60  CALL ymds2ju (year, month, day, sec, julian)
61  WRITE(*,*) ' --> The resulting julian day : ',julian
62  CALL ju2ymds (julian, year, month, day, sec)
63  WRITE(*,*) &
64 &  'The day which comes out again, does it make more sense ? :'
65  WRITE(*,*) 'Year : ',year,' Month : ',month,' Day : ',day
66!-----------------------
67END PROGRAM testcalendar
Note: See TracBrowser for help on using the repository browser.