/[MITgcm]/MITgcm/pkg/cal/cal_set.F
ViewVC logotype

Diff of /MITgcm/pkg/cal/cal_set.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph | View Patch Patch

revision 1.6 by jmc, Tue Mar 16 00:11:46 2010 UTC revision 1.7 by jmc, Tue Apr 3 15:12:21 2012 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "CAL_OPTIONS.h"  #include "CAL_OPTIONS.h"
5    
6        subroutine cal_Set(        SUBROUTINE CAL_SET(
7       I                    modstart,       I                    modstart, modend, modstep,
8       I                    modend,       I                    moditerini, moditerend, modintsteps,
9       I                    modstep,       I                    modstartdate_1, modstartdate_2,
10       I                    modcalendartype,       I                    modcalendartype,
11       I                    modstartdate_1,       I                    myThid )
      I                    modstartdate_2,  
      I                    modenddate_1,  
      I                    modenddate_2,  
      I                    moditerini,  
      I                    moditerend,  
      I                    modintsteps,  
      I                    mythid  
      &                  )  
   
 c     ==================================================================  
 c     SUBROUTINE cal_Set  
 c     ==================================================================  
 c  
 c     o This routine initialises the calendar according to the user  
 c       specifications in "data".  
 c  
 c     Purpose: Precalculations for the calendar.  
 c  
 c              Given the type of calendar that should be used date  
 c              arrays and some additional information is returned.  
 c  
 c              Check for consistency with other specifications such  
 c              as modintsteps.  
 c  
 c     started: Christian Eckert eckert@mit.edu  30-Jun-1999  
 c  
 c     changed: Christian Eckert eckert@mit.edu  29-Dec-1999  
 c  
 c              - restructured the original version in order to have a  
 c                better interface to the MITgcmUV.  
 c  
 c              Christian Eckert eckert@mit.edu  19-Jan-2000  
 c  
 c              - Changed the role of the routine arguments. Chris Hill  
 c                proposed to make the calendar less "invasive". The tool  
 c                now assumes that the MITgcmUV already provides an ade-  
 c                quate set of time stepping parameters. The calendar  
 c                only associates a date with the given starttime of the  
 c                numerical model. startdate corresponds to zero start-  
 c                time. So, given niter0 or startdate .ne. zero the actual  
 c                startdate of the current integration is shifted by the  
 c                time interval correponding to niter0, startdate respec-  
 c                tively.  
 c  
 c              Christian Eckert eckert@mit.edu  03-Feb-2000  
 c  
 c              - Introduced new routine and function names, cal_<NAME>,  
 c                for verion 0.1.3.  
 c  
 c              Christian Eckert eckert@mit.edu  23-Feb-2000  
 c  
 c              - Corrected the declaration of *modelrundate*  
 c                --> integer modelrundate(4)  
 c  
 c     ==================================================================  
 c     SUBROUTINE cal_Set  
 c     ==================================================================  
12    
13        implicit none  C     ==================================================================
14    C     SUBROUTINE cal_Set
15    C     ==================================================================
16    C
17    C     o This routine initialises the calendar according to the user
18    C       specifications in "data".
19    C
20    C     Purpose: Precalculations for the calendar.
21    C
22    C              Given the type of calendar that should be used date
23    C              arrays and some additional information is returned.
24    C
25    C              Check for consistency with other specifications such
26    C              as modintsteps.
27    C
28    C     started: Christian Eckert eckert@mit.edu  30-Jun-1999
29    C
30    C     changed: Christian Eckert eckert@mit.edu  29-Dec-1999
31    C
32    C              - restructured the original version in order to have a
33    C                better interface to the MITgcmUV.
34    C
35    C              Christian Eckert eckert@mit.edu  19-Jan-2000
36    C
37    C              - Changed the role of the routine arguments. Chris Hill
38    C                proposed to make the calendar less "invasive". The tool
39    C                now assumes that the MITgcmUV already provides an ade-
40    C                quate set of time stepping parameters. The calendar
41    C                only associates a date with the given starttime of the
42    C                numerical model. startdate corresponds to zero start-
43    C                time. So, given niter0 or startdate .ne. zero the actual
44    C                startdate of the current integration is shifted by the
45    C                time interval correponding to niter0, startdate respec-
46    C                tively.
47    C
48    C              Christian Eckert eckert@mit.edu  03-Feb-2000
49    C
50    C              - Introduced new routine and function names, cal_<NAME>,
51    C                for verion 0.1.3.
52    C
53    C              Christian Eckert eckert@mit.edu  23-Feb-2000
54    C
55    C              - Corrected the declaration of *modelrundate*
56    C                --> integer modelrundate(4)
57    C
58    C     ==================================================================
59    C     SUBROUTINE cal_Set
60    C     ==================================================================
61    
62  c     == global variables ==        IMPLICIT NONE
63    
64    C     == global variables ==
65    
66  #include "cal.h"  #include "cal.h"
67    
68  c     == routine arguments ==  C     == routine arguments ==
69    
70  c     modcalendartype - the type of calendar that is to be used.  C     modstart        :: start time of the model integration
71  c                       Available: 'model'  C     modend          :: end time of the model integration
72  c                                  'gregorian'  C     modstep         :: timestep of the numerical model
73  c     modstartdate_1  - startdate of the integration: yyyymmdd  C     moditerini      :: initial iteration number of the model
74  c     modstartdate_2  - startdate of the integration: hhmmss  C     moditerend      :: last iteration number of the model
75  c     modenddate_1    - enddate   of the integration: yyyymmdd  C     modintsteps     :: number of timesteps that are to be performed.
76  c     modenddate_2    - enddate   of the integration: hhmmss  C     modstartdate_1  :: startdate of the integration: yyyymmdd
77  c     moditerini      - initial iteration number of the model  C     modstartdate_2  :: startdate of the integration: hhmmss
78  c     moditerend      - last iteration number of the model  C     modcalendartype :: the type of calendar that is to be used.
79  c     modstep         - timestep of the numerical model  C                        Available: 'model' or 'gregorian'
80  c     modintsteps     - number of timesteps that are to be performed.  C     myThid          :: my Thread Id number
81  c     mythid          - number of this instance of the subrotuine.  C-jmc: should remove modenddate_1 & modenddate_2 (always identically zero in
82    C      cal_readparams)
83    
84        _RL     modstart        _RL     modstart
85        _RL     modend        _RL     modend
86        _RL     modstep        _RL     modstep
87        character*(*) modcalendartype        INTEGER moditerini
88        integer modstartdate_1        INTEGER moditerend
89        integer modstartdate_2        INTEGER modintsteps
90        integer modenddate_1        INTEGER modstartdate_1
91        integer modenddate_2        INTEGER modstartdate_2
92        integer moditerini        CHARACTER*(*) modcalendartype
93        integer moditerend        INTEGER myThid
94        integer modintsteps  
95        integer mythid  C     == local variables ==
96          INTEGER i,j,k
97  c     == local variables ==        INTEGER ierr
98          INTEGER timediff(4)
99        integer i,j,k        INTEGER iterinitime(4)
100        integer ierr        INTEGER modelrundate(4)
       integer datediff(4)  
       integer timediff(4)  
       integer iterinitime(4)  
       integer modelrundate(4)  
101        _RL     runtimesecs        _RL     runtimesecs
102        _RL     iterinisecs        _RL     iterinisecs
103    
104  c     == external ==  C     == end of interface ==
   
       integer  cal_IntYears  
       external cal_IntYears  
   
       integer  cal_IntMonths  
       external cal_IntMonths  
   
       integer  cal_IntDays  
       external cal_IntDays  
105    
106        integer  cal_nStepDay  C     Initialise some variables.
       external cal_nStepDay  
   
 c     == end of interface ==  
   
 c     Initialise some variables.  
107        usingNoCalendar        = .false.        usingNoCalendar        = .false.
108        usingGregorianCalendar = .false.        usingGregorianCalendar = .false.
109        usingModelCalendar     = .false.        usingModelCalendar     = .false.
110        usingJulianCalendar    = .false.        usingJulianCalendar    = .false.
111    
112  c     Map the numerical model parameters. --> common blocks in CALENDAR.h  C     Map the numerical model parameters. --> common blocks in CALENDAR.h
113        modelstart       = modstart        modelstart       = modstart
114        modelend         = modend        modelend         = modend
115        modelstep        = modstep        modelstep        = modstep
116        modeliter0       = moditerini        modeliter0       = moditerini
       modelintsteps    = modintsteps  
   
117        modeliterend     = moditerend        modeliterend     = moditerend
118          modelintsteps    = modintsteps
119    
120  c     Do first consistency checks (most are taken from the MITgcmUV).  C     Do first consistency checks
121  c     o Time step.  C     o Time step.
122        if ( modelstep .le. 0. ) then        if ( modelstep .le. 0. ) then
123          ierr = 102          ierr = 102
124          call cal_PrintError( ierr, mythid )          call cal_PrintError( ierr, myThid )
125          stop ' stopped in cal_Set.'          stop ' stopped in cal_Set.'
126        endif        endif
127        if ( modelstep .lt. 1. ) then        if ( modelstep .lt. 1. ) then
128          ierr = 103          ierr = 103
129          call cal_PrintError( ierr, mythid )          call cal_PrintError( ierr, myThid )
130          stop ' stopped in cal_Set.'          stop ' stopped in cal_Set.'
131        endif        endif
132        if ( abs(modelstep - nint(modelstep)) .gt. 0.000001 ) then        if ( abs(modelstep - nint(modelstep)) .gt. 0.000001 ) then
133          ierr = 104          ierr = 104
134          call cal_PrintError( ierr, mythid )          call cal_PrintError( ierr, myThid )
135          stop ' stopped in cal_Set.'          stop ' stopped in cal_Set.'
136        else        else
137          modelstep = float(nint(modelstep))          modelstep = float(nint(modelstep))
138        endif        endif
139    
140  c     o Start time  C     o Start time
141        if ( modeliter0 .ne. 0 .and. modelstart .eq. 0. ) then  c     if ( modeliter0 .ne. 0 .and. modelstart .eq. 0. ) then
142           modelstart = modelstep*float(modeliter0)  c        modelstart = modelstep*float(modeliter0)
143        endif  c     endif
144  c     o modeliter0  C     o modeliter0
145        if ( modeliter0 .eq. 0 .and. modelstart .ne. 0. ) then  c     if ( modeliter0 .eq. 0 .and. modelstart .ne. 0. ) then
146           modeliter0 = int( modelstart/modelstep )  c        modeliter0 = int( modelstart/modelstep )
147        endif  c     endif
148    
149    C     o modelintsteps
150    c     if ( modelintsteps .eq. 0 .and. modeliterend .ne. 0 )
151    c    &     modelintsteps = modeliterend - modeliter0
152    c     if ( modelintsteps .eq. 0 .and. modelend .ne. 0. )
153    c    &     modelintsteps = int(0.5 + (modelend - modelstart)/modelstep)
154    
155    C     o modeliterend
156    c     if ( modeliterend .eq. 0 .and. modelintsteps .ne. 0 )
157    c    &     modeliterend = modeliter0 + modelintsteps
158    c     if ( modeliterend .eq. 0 .and. modelend .ne. 0. )
159    c    &     modeliterend = int(0.5 + modelend/modelstep)
160    
161    C     o modelend
162    c     if ( modelend .eq. 0. .and. modelintsteps .ne. 0 )
163    c    &     modelend = modelstart + modelstep*float(modelintsteps)
164    c     if ( modelend .eq. 0. .and. modeliterend .ne. 0 )
165    c    &     modelend = modelstep*float(modeliterend)
166    
167  c     o modelintsteps  C     Start setting the calendar parameters.
       if ( modelintsteps .eq. 0 .and. modeliterend .ne. 0 )  
      &     modelintsteps = modeliterend - modeliter0  
       if ( modelintsteps .eq. 0 .and. modelend .ne. 0. )  
      &     modelintsteps = int(0.5 + (modelend - modelstart)/modelstep)  
   
 c     o modeliterend  
       if ( modeliterend .eq. 0 .and. modelintsteps .ne. 0 )  
      &     modeliterend = modeliter0 + modelintsteps  
       if ( modeliterend .eq. 0 .and. modelend .ne. 0. )  
      &     modeliterend = int(0.5 + modelend/modelstep)  
   
 c     o modelend  
       if ( modelend .eq. 0. .and. modelintsteps .ne. 0 )  
      &     modelend = modelstart + modelstep*float(modelintsteps)  
       if ( modelend .eq. 0. .and. modeliterend .ne. 0 )  
      &     modelend = modelstep*float(modeliterend)  
168    
169  c     Start setting the calendar parameters.  C     The calendar type.
   
 c     The calendar type.  
170        if ( modcalendartype .eq. 'none') then        if ( modcalendartype .eq. 'none') then
171          usingNoCalendar = .true.          usingNoCalendar = .true.
172        endif        endif
# Line 207  c     The calendar type. Line 181  c     The calendar type.
181        endif        endif
182    
183        if ( usingGregorianCalendar ) then        if ( usingGregorianCalendar ) then
184  c       The reference date for the Gregorian Calendar.  C       The reference date for the Gregorian Calendar.
185  c       and its format: ( yymmdd , hhmmss , leap year, weekday )  C       and its format: ( yymmdd , hhmmss , leap year, weekday )
186  c                                             (1/2)    (1 - 7)  C                                             (1/2)    (1 - 7)
187  c       The Gregorian calendar starts on Friday, 15 Oct. 1582.  C       The Gregorian calendar starts on Friday, 15 Oct. 1582.
188          refdate(1) = 15821015          refdate(1) = 15821015
189          refdate(2) = 0          refdate(2) = 0
190          refdate(3) = 1          refdate(3) = 1
191          refdate(4) = 1          refdate(4) = 1
192    
193  c       Number of months per year and other useful numbers.  C       Number of months per year and other useful numbers.
194          nmonthyear       = 12          nmonthyear       = 12
195          ndaysnoleap      = 365          ndaysnoleap      = 365
196          ndaysleap        = 366          ndaysleap        = 366
# Line 228  c       Number of months per year and ot Line 202  c       Number of months per year and ot
202          secondsperhour   = 3600          secondsperhour   = 3600
203          secondsperminute = 60          secondsperminute = 60
204    
205  c       Number of days per month.  C       Number of days per month.
206  c       The "magic" number 2773 derives from the sequence: 101010110101  C       The "magic" number 2773 derives from the sequence: 101010110101
207  c         read in reverse and interpreted as a dual number. An  C         read in reverse and interpreted as a dual number. An
208  c         alternative would be to take 2741 with the loop being  C         alternative would be to take 2741 with the loop being
209  c         executed in reverse order. Accidentially, the latter  C         executed in reverse order. Accidentially, the latter
210  c         is a prime number.  C         is a prime number.
211          k=2773          k=2773
212          do i=1,nmonthyear          do i=1,nmonthyear
213            j = mod(k,2)            j = mod(k,2)
# Line 244  c         is a prime number. Line 218  c         is a prime number.
218          ndaymonth(2,1) = 28          ndaymonth(2,1) = 28
219          ndaymonth(2,2) = 29          ndaymonth(2,2) = 29
220    
221  c       Week days.  C       Week days.
222          dayofweek(1) = 'FRI'          dayofweek(1) = 'FRI'
223          dayofweek(2) = 'SAT'          dayofweek(2) = 'SAT'
224          dayofweek(3) = 'SUN'          dayofweek(3) = 'SUN'
# Line 254  c       Week days. Line 228  c       Week days.
228          dayofweek(7) = 'THU'          dayofweek(7) = 'THU'
229    
230        else if ( usingModelCalendar ) then        else if ( usingModelCalendar ) then
231  c       Assume a model calendar having 12 months with thirty days each.  C       Assume a model calendar having 12 months with thirty days each.
232  c       Reference date is the first day of year 0 at 0am, and model  C       Reference date is the first day of year 0 at 0am, and model
233  c       day 1.  C       day 1.
234          refdate(1) = 00000101          refdate(1) = 00000101
235          refdate(2) = 0          refdate(2) = 0
236          refdate(3) = 1          refdate(3) = 1
237          refdate(4) = 1          refdate(4) = 1
238    
239  c       Some useful numbers.  C       Some useful numbers.
240          nmonthyear       = 12          nmonthyear       = 12
241          ndaysnoleap      = 360          ndaysnoleap      = 360
242          ndaysleap        = 360          ndaysleap        = 360
# Line 278  c       Some useful numbers. Line 252  c       Some useful numbers.
252            ndaymonth(i,2) = 30            ndaymonth(i,2) = 30
253          enddo          enddo
254    
255  c       Week days (Model Day 1 - 7).  C       Week days (Model Day 1 - 7).
256          dayofweek(1) = 'MD1'          dayofweek(1) = 'MD1'
257          dayofweek(2) = 'MD2'          dayofweek(2) = 'MD2'
258          dayofweek(3) = 'MD3'          dayofweek(3) = 'MD3'
# Line 287  c       Week days (Model Day 1 - 7). Line 261  c       Week days (Model Day 1 - 7).
261          dayofweek(6) = 'MD6'          dayofweek(6) = 'MD6'
262          dayofweek(7) = 'MD7'          dayofweek(7) = 'MD7'
263    
264        else if ( usingJulianCalendar ) then  c     else if ( usingJulianCalendar ) then
265    c       stop ' stopped in cal_Set (Julian Calendar).'
266          ierr = 110  c     else if ( usingNoCalendar ) then
267          call cal_PrintError( ierr, mythid )  c       stop ' stopped in cal_Set (No Calendar).'
   
         refdate(1) =   -4370  
         refdate(2) = -120000  
         refdate(3) =       0  
         refdate(4) =      -1  
   
 c       Some useful numbers.  
         nmonthyear       = 12  
         ndaysnoleap      = 0  
         ndaysleap        = 0  
         nmaxdaymonth     = 0  
         hoursperday      = 24  
         minutesperday    = 1440  
         minutesperhour   = 60  
         secondsperday    = 86400  
         secondsperhour   = 3600  
         secondsperminute = 60  
         do i=1,nmonthyear  
           ndaymonth(i,1) = 0  
           ndaymonth(i,2) = 0  
         enddo  
         stop ' stopped in cal_Set (Julian Calendar).'  
   
       else if ( usingNoCalendar ) then  
   
         ierr = 111  
         call cal_PrintError( ierr, mythid )  
   
         refdate(1) =  0  
         refdate(2) =  0  
         refdate(3) =  0  
         refdate(4) = -1  
   
 c       Some useful numbers.  
         nmonthyear       = 12  
         ndaysnoleap      = 0  
         ndaysleap        = 0  
         nmaxdaymonth     = 0  
         hoursperday      = 24  
         minutesperday    = 1440  
         minutesperhour   = 60  
         secondsperday    = 86400  
         secondsperhour   = 3600  
         secondsperminute = 60  
         do i=1,nmonthyear  
           ndaymonth(i,1) = 0  
           ndaymonth(i,2) = 0  
         enddo  
   
         stop ' stopped in cal_Set (No Calendar).'  
   
268        else        else
   
269          ierr = 101          ierr = 101
270          call cal_PrintError( ierr, mythid )          call cal_PrintError( ierr, myThid )
271          stop          stop
   
272        endif        endif
273    
274  c     A next set of checks of the user specifications.  C     A next set of checks of the user specifications.
275  c     Number of possible modelsteps per calendar day.  C     Number of possible modelsteps per calendar day.
276        modelstepsperday = cal_nStepDay(mythid)  C-jmc: modelstepsperday is not used and can be removed
277    c     modelstepsperday = cal_nStepDay(mythid)
278  cdm   if (modelstepsperday .eq. 0 ) then  cdm   if (modelstepsperday .eq. 0 ) then
279  cdm     ierr = 105  cdm     ierr = 105
280  cdm     call cal_PrintError( ierr, mythid )  cdm     call cal_PrintError( ierr, mythid )
281  cdm     stop ' stopped in cal_Set.'  cdm     stop ' stopped in cal_Set.'
282  cdm   endif  cdm   endif
283    
284  c     Complete the start date specification to get a full date array.  C     Complete the start date specification to get a full date array.
285        call cal_FullDate( modstartdate_1, modstartdate_2,        call cal_FullDate( modstartdate_1, modstartdate_2,
286       &                   modelstartdate, mythid )       &                   modelstartdate, myThid )
287    
288  c     From here on, the final calendar settings are determined by the  C     From here on, the final calendar settings are determined by the
289  c     following variables:  C     following variables:
290  c  C
291  c           modelstep, modelstart, modelstartdate, and modeliter0.  C           modelstep, modelstart, modelstartdate, and modeliter0.
292    C-jmc: simplify so that calendar settings only function of:
293  c     Two scenarios are allowed:  C           modelstart, modelstep*modelintsteps & modelstartdate
294  c  
295  c     First case:  modelintsteps is given as well, modelenddate is  C     Two scenarios are allowed:
296  c                  set to zero.  C
297  c     Second case: modelintsteps is set to zero, modelenddate is given.  C     First case:  modelintsteps is given as well, modelenddate is
298    C                  set to zero.
299        if ( (modelintsteps   .ne. 0)    .and.  C     Second case: modelintsteps is set to zero, modelenddate is given.
300       &     ( (modenddate_1 .eq. 0)     .and.  C-jmc: can only be 1rst case since modelintsteps (coming from model)
301       &       (modenddate_2 .eq. 0) ) ) then  C      is always set and modenddate_1 & 2 are always zero.
302    
303          runtimesecs = float(modelintsteps)*modelstep  c     if ( (modelintsteps   .ne. 0)    .and.
304          modelend    = modelstart + runtimesecs  c    &     ( (modenddate_1 .eq. 0)     .and.
305    c    &       (modenddate_2 .eq. 0) ) ) then
306        else if ( (modelintsteps   .eq. 0)        .and.  
307       &          (.not. ( (modenddate_1 .eq. 0 ) .and.          runtimesecs = modelintsteps*modelstep
308       &                   (modenddate_2 .eq. 0) ) ) ) then  C-jmc: no need to reset modelend !
309    c       modelend    = modelstart + runtimesecs
310          call cal_FullDate( modenddate_1, modenddate_2, modelenddate,  
311       &                     mythid )  c     else
312          call cal_TimePassed( modelstartdate, modelenddate, datediff,  c      CALL PRINT_ERROR('S/R CAL_SET: you win ! error 106 !!!',myThid)
313       &                       mythid )  c       ierr = 106
314          call cal_ToSeconds( datediff, runtimesecs, mythid )  c       call cal_PrintError( ierr, mythid )
315    c       stop ' stopped in cal_Set.'
316          if ( runtimesecs .lt. 0.) then  c     endif
317            ierr = 107  
318            call cal_PrintError( ierr, mythid )  C     Determine the startdate of the integration.
319            stop ' stopped in cal_Set.'  C     (version 0.1.3 >> START << )
320          endif  c     iterinisecs = float(modeliter0)*modelstep
321    C-jmc: above does not work if baseTime <> 0 ; fix it below:
322          modelintsteps = int(runtimesecs/modelstep)        iterinisecs = modelstart
323          runtimesecs   = modelintsteps*modelstep        call cal_TimeInterval( iterinisecs, 'secs', iterinitime, myThid )
         modelend      = modelstart + runtimesecs  
   
       else  
         ierr = 106  
         call cal_PrintError( ierr, mythid )  
         stop ' stopped in cal_Set.'  
       endif  
   
 c     Determine the startdate of the integration.  
 c     (version 0.1.3 >> START << )  
       iterinisecs = float(modeliter0)*modelstep  
       call cal_TimeInterval( iterinisecs, 'secs', iterinitime, mythid )  
324        call cal_AddTime( modelstartdate, iterinitime, modelrundate,        call cal_AddTime( modelstartdate, iterinitime, modelrundate,
325       &                  mythid )       &                  myThid )
326        call cal_CopyDate( modelrundate, modelstartdate, mythid )        call cal_CopyDate( modelrundate, modelstartdate, myThid )
327  c     (version 0.1.3 >> END << )  C     (version 0.1.3 >> END << )
328    
329        call cal_TimeInterval( runtimesecs, 'secs', timediff, mythid )        call cal_TimeInterval( runtimesecs, 'secs', timediff, myThid )
330        call cal_AddTime( modelstartdate, timediff, modelenddate,        call cal_AddTime( modelstartdate, timediff, modelenddate,
331       &                  mythid )       &                  myThid )
   
       modeliterend = modeliter0 + modelintsteps  
332    
333  c     Check consistency of the numerical model and the calendar tool.  C-jmc: no need to reset modeliterend !
334        if ( modelstart .ne. modstart) then  c     modeliterend = modeliter0 + modelintsteps
         ierr = 112  
         call cal_PrintError( ierr, mythid )  
         stop ' stopped in cal_Set.'  
       else if ( modelend .ne. modend ) then  
         ierr = 113  
         call cal_PrintError( ierr, mythid )  
         stop ' stopped in cal_Set.'  
       else if ( modelstep .ne. modstep ) then  
         ierr = 114  
         call cal_PrintError( ierr, mythid )  
         stop ' stopped in cal_Set.'  
       else if ( modeliter0 .ne. moditerini ) then  
         ierr = 115  
         call cal_PrintError( ierr, mythid )  
         stop ' stopped in cal_Set.'  
       else if ( modeliterend .ne. moditerend ) then  
         ierr = 116  
         call cal_PrintError( ierr, mythid )  
         stop ' stopped in cal_Set.'  
       else if ( modelintsteps .ne. modintsteps) then  
         ierr = 117  
         call cal_PrintError( ierr, mythid )  
         stop ' stopped in cal_Set.'  
       endif  
335    
336        return  C     Check consistency of the numerical model and the calendar tool.
337        end  C-jmc: all model time/iter were set earlier and have not been changed
338    C-jmc ==> removed
339    c     if ( modelstart .ne. modstart) then
340    c       ierr = 112
341    c       call cal_PrintError( ierr, mythid )
342    c       stop ' stopped in cal_Set.'
343    c     else if ( modelend .ne. modend ) then
344    c       ierr = 113
345    c       call cal_PrintError( ierr, mythid )
346    c       stop ' stopped in cal_Set.'
347    c     else if ( modelstep .ne. modstep ) then
348    c       ierr = 114
349    c       call cal_PrintError( ierr, mythid )
350    c       stop ' stopped in cal_Set.'
351    c     else if ( modeliter0 .ne. moditerini ) then
352    c       ierr = 115
353    c       call cal_PrintError( ierr, mythid )
354    c       stop ' stopped in cal_Set.'
355    c     else if ( modeliterend .ne. moditerend ) then
356    c       ierr = 116
357    c       call cal_PrintError( ierr, mythid )
358    c       stop ' stopped in cal_Set.'
359    c     else if ( modelintsteps .ne. modintsteps) then
360    c       ierr = 117
361    c       call cal_PrintError( ierr, mythid )
362    c       stop ' stopped in cal_Set.'
363    c     endif
364    
365          RETURN
366          END

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.7

  ViewVC Help
Powered by ViewVC 1.1.22