source: trunk/WRF.COMMON/WRFV2/external/esmf_time_f90/ESMF_Calendar.F90 @ 3602

Last change on this file since 3602 was 11, checked in by aslmd, 14 years ago

spiga@svn-planeto:ajoute le modele meso-echelle martien

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