/[lmdze]/trunk/IOIPSL/Calendar/ioconf_calendar.f
ViewVC logotype

Contents of /trunk/IOIPSL/Calendar/ioconf_calendar.f

Parent Directory Parent Directory | Revision Log Revision Log


Revision 92 - (show annotations)
Wed Mar 26 18:16:05 2014 UTC (10 years, 1 month ago) by guez
File size: 3553 byte(s)
Extracted procedures that were in module calendar into separate files.

1 module ioconf_calendar_m
2
3 implicit none
4
5 contains
6
7 SUBROUTINE ioconf_calendar (str)
8
9 ! This routine allows to configure the calendar to be used.
10 ! This operation is only allowed once and the first call to
11 ! ymds2ju or ju2ymsd will lock the current configuration.
12 ! the argument to ioconf_calendar can be any of the following:
13 ! - gregorian: This is the gregorian calendar (default here)
14 ! - noleap: A calendar without leap years = 365 days
15 ! - xxxd: A calendar of xxx days (has to be a modulo of 12)
16 ! with 12 month of equal length
17
18 use calendar, only: mon_len, calendar_used, lock_unan, un_an
19 use strlowercase_m
20 use errioipsl
21
22 CHARACTER(LEN=*), INTENT(IN):: str
23
24 INTEGER:: leng, ipos
25 CHARACTER(LEN=10):: str10
26 !--------------------------------------------------------------------
27
28 ! 1.0 Clean up the sring !
29
30 CALL strlowercase (str)
31
32 IF (.NOT.lock_unan) THEN
33
34 lock_unan=.TRUE.
35
36 SELECT CASE(str)
37 CASE('gregorian')
38 calendar_used = 'gregorian'
39 un_an = 365.2425
40 mon_len(:)=(/31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
41 CASE('standard')
42 calendar_used = 'gregorian'
43 un_an = 365.2425
44 mon_len(:)=(/31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
45 CASE('proleptic_gregorian')
46 calendar_used = 'gregorian'
47 un_an = 365.2425
48 mon_len(:)=(/31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
49 CASE('noleap')
50 calendar_used = 'noleap'
51 un_an = 365.0
52 mon_len(:)=(/31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
53 CASE('365_day')
54 calendar_used = 'noleap'
55 un_an = 365.0
56 mon_len(:)=(/31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
57 CASE('365d')
58 calendar_used = 'noleap'
59 un_an = 365.0
60 mon_len(:)=(/31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
61 CASE('all_leap')
62 calendar_used = 'all_leap'
63 un_an = 366.0
64 mon_len(:)=(/31, 29, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
65 CASE('366_day')
66 calendar_used = 'all_leap'
67 un_an = 366.0
68 mon_len(:)=(/31, 29, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
69 CASE('366d')
70 calendar_used = 'all_leap'
71 un_an = 366.0
72 mon_len(:)=(/31, 29, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31/)
73 CASE DEFAULT
74 ipos = INDEX(str, 'd')
75 IF (ipos == 4) THEN
76 READ(str(1:3), '(I3)') leng
77 IF ( (MOD(leng, 12) == 0).AND.(leng > 1) ) THEN
78 calendar_used = str
79 un_an = leng
80 mon_len(:) = leng
81 ELSE
82 CALL histerr (3, 'ioconf_calendar', &
83 & 'The length of the year as to be a modulo of 12', &
84 & 'so that it can be divided into 12 month of equal length', &
85 & str)
86 ENDIF
87 ELSE
88 CALL histerr (3, 'ioconf_calendar', &
89 & 'Unrecognized input, please ceck the man pages.', str, ' ')
90 ENDIF
91 END SELECT
92 ELSE
93 WRITE(str10, '(f10.4)') un_an
94 CALL histerr (2, 'ioconf_calendar', &
95 & 'The calendar was already used or configured. You are not', &
96 & 'allowed to change it again. '// &
97 & 'The following length of year is used:', str10)
98 ENDIF
99
100 END SUBROUTINE ioconf_calendar
101
102 end module ioconf_calendar_m

  ViewVC Help
Powered by ViewVC 1.1.21