updated top-level README and version_decl for V4.4.2 (#1795)
[WRF.git] / external / esmf_time_f90 / ESMF_Calendar.F90
blob0ee619d2a58bde7f7b6f9fe2586c42a267b3d0d3
2 !==============================================================================
4 !     ESMF Calendar Module
5       module WRF_ESMF_CalendarMod
7 !==============================================================================
9 ! This file contains the Calendar class definition and all Calendar class
10 ! methods.
12 !------------------------------------------------------------------------------
13 ! INCLUDES
14 #include <ESMF_TimeMgr.inc>
16 !==============================================================================
17 !BOPI
18 ! !MODULE: WRF_ESMF_CalendarMod
20 ! !DESCRIPTION:
21 ! Part of Time Manager F90 API wrapper of C++ implemenation
23 ! Defines F90 wrapper entry points for corresponding
24 ! C++ class { \tt ESMC\_Calendar} implementation
26 ! See {\tt ../include/ESMC\_Calendar.h} for complete description
28 !------------------------------------------------------------------------------
29 ! !USES:
30       ! inherit from ESMF base class
31       use WRF_ESMF_BaseMod
33       ! inherit from base time class
34       use WRF_ESMF_BaseTimeMod
36       implicit none
38 !------------------------------------------------------------------------------
39 ! !PRIVATE TYPES:
40       private
41 !------------------------------------------------------------------------------
45       INTEGER, PARAMETER :: MONTHS_PER_YEAR = 12
46       INTEGER, PARAMETER :: mday(MONTHS_PER_YEAR)   &
47                           = (/31,28,31,30,31,30,31,31,30,31,30,31/)
48       INTEGER, PARAMETER :: mdayleap(MONTHS_PER_YEAR) &
49                           = (/31,29,31,30,31,30,31,31,30,31,30,31/)
50       INTEGER, DIMENSION(365) :: daym
51       INTEGER, DIMENSION(366) :: daymleap
52       INTEGER :: mdaycum(0:MONTHS_PER_YEAR)
53       INTEGER :: mdayleapcum(0:MONTHS_PER_YEAR)
54       TYPE(ESMF_BaseTime), TARGET :: monthbdys(0:MONTHS_PER_YEAR)
55       TYPE(ESMF_BaseTime), TARGET :: monthbdysleap(0:MONTHS_PER_YEAR)
58 !------------------------------------------------------------------------------
59 !     ! ESMF_CalendarType
61 !     ! F90 "enum" type to match C++ ESMC_CalendarType enum
63       type ESMF_CalendarType
64       private
65         integer :: caltype
66       end type
68       type(ESMF_CalendarType), parameter :: &
69                                ESMF_CAL_GREGORIAN =  ESMF_CalendarType(1), &
70                                ESMF_CAL_JULIAN =     ESMF_CalendarType(2), &
71                            ! like Gregorian, except Feb always has 28 days
72                                ESMF_CAL_NOLEAP =     ESMF_CalendarType(3), & 
73                            ! 12 months, 30 days each
74                                ESMF_CAL_360DAY =     ESMF_CalendarType(4), & 
75                            ! user defined
76                                ESMF_CAL_GENERIC =    ESMF_CalendarType(5), &
77                            ! track base time seconds only
78                                ESMF_CAL_NOCALENDAR = ESMF_CalendarType(6)
80 !------------------------------------------------------------------------------
81 !     ! ESMF_Calendar
83 !     ! F90 class type to match C++ Calendar class in size only;
84 !     !  all dereferencing within class is performed by C++ implementation
86 !------------------------------------------------------------------------------
88 !     ! ESMF_DaysPerYear
90       type ESMF_DaysPerYear
91       private
92         integer :: D        ! whole days per year
93 ! Fractional days-per-year are not yet used in this implementation.  
94 !        integer :: Dn       ! fractional days per year numerator
95 !        integer :: Dd       ! fractional days per year denominator
96       end type              ! e.g. for Venus, D=0, Dn=926, Dd=1000
98 !------------------------------------------------------------------------------
99 !     ! ESMF_Calendar
102       type ESMF_Calendar
103       private
104         type(ESMF_CalendarType) :: Type
105 ! TBH:  When NO_DT_COMPONENT_INIT is set, code that uses F95 compile-time 
106 ! TBH:  initialization of components of derived types is not included.  
107 ! TBH:  Some older compilers, like PGI 5.x do not support this F95 feature.  
108 #ifdef NO_DT_COMPONENT_INIT
109         logical :: Set
110 #else
111         logical :: Set = .false.
112 #endif
113         integer, dimension(MONTHS_PER_YEAR) :: DaysPerMonth
114         integer :: SecondsPerDay
115         integer :: SecondsPerYear
116         type(ESMF_DaysPerYear) :: DaysPerYear
117       end type
119 !------------------------------------------------------------------------------
120 ! !PUBLIC DATA:
121    TYPE(ESMF_Calendar), public, save, pointer :: defaultCal   ! Default Calendar
125 !------------------------------------------------------------------------------
126 ! !PUBLIC TYPES:
127       public MONTHS_PER_YEAR
128       public mday
129       public mdayleap
130       public monthbdys
131       public monthbdysleap
132       public daym
133       public daymleap
134       public mdaycum
135       public mdayleapcum
136       public ESMF_CalendarType
137       public ESMF_CAL_GREGORIAN, ESMF_CAL_NOLEAP, &
138              ESMF_CAL_360DAY, ESMF_CAL_NOCALENDAR
139 !      public ESMF_CAL_JULIAN
140 !      public ESMF_CAL_GENERIC
141       public ESMF_Calendar
143 !------------------------------------------------------------------------------
145 ! !PUBLIC MEMBER FUNCTIONS:
146       public ESMF_CalendarCreate
148 ! Required inherited and overridden ESMF_Base class methods
150       public ESMF_CalendarInitialized ! Only in this implementation, intended
151                                       ! to be private within ESMF methods
152 !EOPI
154 !==============================================================================
156       contains
159 !==============================================================================
160 !BOP
161 ! !IROUTINE: ESMF_CalendarCreate - Create a new ESMF Calendar of built-in type
163 ! !INTERFACE:
164       ! Private name; call using ESMF_CalendarCreate()
165       function ESMF_CalendarCreate(name, calendartype, rc)
167 ! !RETURN VALUE:
168       type(ESMF_Calendar) :: ESMF_CalendarCreate
170 ! !ARGUMENTS:
171       character (len=*),       intent(in),  optional :: name
172       type(ESMF_CalendarType), intent(in)            :: calendartype
173       integer,                 intent(out), optional :: rc
175 ! !DESCRIPTION:
176 !     Creates and sets a {\tt calendar} to the given built-in
177 !     {\tt ESMF\_CalendarType}. 
179 !     This is a private method; invoke via the public overloaded entry point
180 !     {\tt ESMF\_CalendarCreate()}.
182 !     The arguments are:
183 !     \begin{description}
184 !     \item[{[name]}]
185 !          The name for the newly created calendar.  If not specified, a
186 !          default unique name will be generated: "CalendarNNN" where NNN
187 !          is a unique sequence number from 001 to 999.
188 !     \item[calendartype]
189 !          The built-in {\tt ESMF\_CalendarType}.  Valid values are:
190 !            {\tt ESMF\_CAL\_360DAY}, {\tt ESMF\_CAL\_GREGORIAN},
191 !            {\tt ESMF\_CAL\_JULIANDAY}, {\tt ESMF\_CAL\_NOCALENDAR}, and
192 !            {\tt ESMF\_CAL\_NOLEAP}.
193 !          See the "Time Manager Reference" document for a description of
194 !          each calendar type.
195 !     \item[{[rc]}]
196 !          Return code; equals {\tt ESMF\_SUCCESS} if there are no errors.
197 !     \end{description}
198 !    
199 !EOP
200 ! !REQUIREMENTS:
201 !     TMGn.n.n
202       type(ESMF_DaysPerYear) :: dayspy
204       if ( present(rc) ) rc = ESMF_FAILURE
205 ! Calendar type is hard-coded.  Use ESMF library if more flexibility is 
206 ! needed.  
207 #ifdef NO_LEAP_CALENDAR
208       if ( calendartype%caltype  /= ESMF_CAL_NOLEAP%caltype ) then
209          write(6,*) 'Not a valid calendar type for this implementation'
210          write(6,*) 'This implementation only allows ESMF_CAL_NOLEAP'
211          write(6,*) 'calender type set to     = ', calendartype%caltype
212          write(6,*) 'NO_LEAP calendar type is = ', ESMF_CAL_NOLEAP%caltype
213          return
214       end if
215       ESMF_CalendarCreate%Type = ESMF_CAL_NOLEAP
216 #else
217       if ( calendartype%caltype  /= ESMF_CAL_GREGORIAN%caltype ) then
218          write(6,*) 'Not a valid calendar type for this implementation'
219          write(6,*) 'This implementation only allows ESMF_CAL_GREGORIAN'
220          write(6,*) 'calender type set to     = ', calendartype%caltype
221          write(6,*) 'GREGORIAN calendar type is = ', ESMF_CAL_GREGORIAN%caltype
222          return
223       end if
224       ESMF_CalendarCreate%Type = ESMF_CAL_GREGORIAN
225 #endif
226 ! This is a bug on some systems -- need initial value set by compiler at 
227 ! startup.  
228 ! However, note that some older compilers do not support compile-time 
229 ! initialization of data members of Fortran derived data types.  For example, 
230 ! PGI 5.x compilers do not support this F95 feature.  See 
231 ! NO_DT_COMPONENT_INIT.  
232       ESMF_CalendarCreate%Set = .true.
233       ESMF_CalendarCreate%SecondsPerDay = SECONDS_PER_DAY
234 ! DaysPerYear and SecondsPerYear are incorrect for Gregorian calendars...  
235       dayspy%D = size(daym)
236 !TBH:  TODO:  Replace DaysPerYear and SecondsPerYear with methods 
237 !TBH:  TODO:  since they only make sense for the NO_LEAP calendar!  
238       ESMF_CalendarCreate%DaysPerYear = dayspy
239       ESMF_CalendarCreate%SecondsPerYear = ESMF_CalendarCreate%SecondsPerDay &
240                                        * dayspy%D
241 !TBH:  TODO:  use mdayleap for leap-year calendar
242       ESMF_CalendarCreate%DaysPerMonth(:) = mday(:)
244       if ( present(rc) ) rc = ESMF_SUCCESS
246       end function ESMF_CalendarCreate
249 !==============================================================================
250 !BOP
251 ! !IROUTINE: ESMF_CalendarInitialized - check if calendar was created
253 ! !INTERFACE:
254       function ESMF_CalendarInitialized(calendar)
256 ! !RETURN VALUE:
257       logical ESMF_CalendarInitialized
259 ! !ARGUMENTS:
260       type(ESMF_Calendar), intent(in)            :: calendar
262 ! !DESCRIPTION:
263 !EOP
264 ! !REQUIREMENTS:
265 !     TMGn.n.n
266 ! Note that return value from this function will be bogus for older compilers 
267 ! that do not support compile-time initialization of data members of Fortran 
268 ! derived data types.  For example, PGI 5.x compilers do not support this F95 
269 ! feature.  At the moment, the call to this fuction is #ifdefd out when the 
270 ! leap-year calendar is used so this is not an issue for WRF (see 
271 ! NO_DT_COMPONENT_INIT).  
272         ESMF_CalendarInitialized = calendar%set
274      end function ESMF_CalendarInitialized
276       end module WRF_ESMF_CalendarMod