New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 1291 – NEMO

Changeset 1291


Ignore:
Timestamp:
2009-02-03T15:22:22+01:00 (15 years ago)
Author:
cetlod
Message:

update modules, see ticket:320

Location:
trunk/NEMO/OFF_SRC
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OFF_SRC/daymod.F90

    r1265 r1291  
    44   !! Ocean        :  calendar  
    55   !!===================================================================== 
     6   !! History :        !  94-09  (M. Pontaud M. Imbard)  Original code 
     7   !!                  !  97-03  (O. Marti) 
     8   !!                  !  97-05  (G. Madec)  
     9   !!                  !  97-08  (M. Imbard) 
     10   !!             9.0  !  03-09  (G. Madec)  F90 + nyear, nmonth, nday 
     11   !!                  !  04-01  (A.M. Treguier) new calculation based on adatrj 
     12   !!                  !  06-08  (G. Madec)  surface module major update 
     13   !!----------------------------------------------------------------------       
    614 
    715   !!---------------------------------------------------------------------- 
    816   !!   day        : calendar 
    9    !!---------------------------------------------------------------------- 
    10    !! * Modules used 
     17   !!   
     18   !!           ------------------------------- 
     19   !!           ----------- WARNING ----------- 
     20   !! 
     21   !!   we suppose that the time step is deviding the number of second of in a day 
     22   !!             ---> MOD( rday, rdttra(1) ) == 0 
     23   !! 
     24   !!           ----------- WARNING ----------- 
     25   !!           ------------------------------- 
     26   !!   
     27   !!---------------------------------------------------------------------- 
    1128   USE dom_oce         ! ocean space and time domain 
    1229   USE phycst          ! physical constants 
    1330   USE in_out_manager  ! I/O manager 
     31   USE prtctl          ! Print control 
    1432 
    1533   IMPLICIT NONE 
    1634   PRIVATE 
    1735 
    18    !! * Routine accessibility 
    1936   PUBLIC day        ! called by step.F90 
    20  
    21    !! * Shared module variables 
    22    INTEGER , PUBLIC ::   &  !: 
    23       nyear     ,   &  !: current year 
    24       nmonth    ,   &  !: current month 
    25       nday      ,   &  !: current day of the month 
    26       nday_year ,   &  !: curent day counted from jan 1st of the current year 
    27       ndastp           !: time step date in year/month/day aammjj 
    28  
    29    REAL(wp), PUBLIC ::   &  !: 
    30        adatrj   ,   &  !: number of elapsed days since the begining of the run 
    31        adatrj0         !: value of adatrj at nit000-1 (before the present run). 
    32        !               !  it is the accumulated duration of previous runs 
    33        !               !  that may have been run with different time steps. 
    34  
     37   PUBLIC day_init   ! called by istate.F90 
     38 
     39   INTEGER , PUBLIC ::   nyear       !: current year 
     40   INTEGER , PUBLIC ::   nmonth      !: current month 
     41   INTEGER , PUBLIC ::   nday        !: current day of the month 
     42   INTEGER , PUBLIC ::   ndastp      !: time step date in yyyymmdd format 
     43   INTEGER , PUBLIC ::   nday_year   !: current day counted from jan 1st of the current year 
     44   REAL(wp), PUBLIC ::   rsec_year   !: current time step counted in second since 00h jan 1st of the current year 
     45   REAL(wp), PUBLIC ::   rsec_month  !: current time step counted in second since 00h 1st day of the current month 
     46   REAL(wp), PUBLIC ::   rsec_day    !: current time step counted in second since 00h of the current day 
     47 
     48   REAL(wp), PUBLIC ::   adatrj      !: number of elapsed days since the begining of the run 
     49   !                                 !: it is the accumulated duration of previous runs 
     50   !                                 !: that may have been run with different time steps. 
     51   INTEGER , PUBLIC, DIMENSION(0:1)  ::   nyear_len    !: length in days of the previous/current year 
     52   INTEGER , PUBLIC, DIMENSION(0:13) ::   nmonth_len   !: length in days of the months of the current year 
     53   REAL(wp), PUBLIC, DIMENSION(0:13) ::   rmonth_half  !: second since the beginning of the year and the halft of the months 
     54   REAL(wp), PUBLIC, DIMENSION(0:13) ::   rmonth_end   !: second since the beginning of the year and the end of the months 
     55   REAL(wp), PUBLIC                  ::   sec1jan000   !: second since Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year 
     56 
     57   ! this two variables are wrong DO NOT USE THEM !!! 
    3558   INTEGER, PUBLIC, DIMENSION(12) ::   nbiss = (/ 31, 29, 31, 30, 31, 30,    &  !: number of days per month 
    3659      &                                           31, 31, 30, 31, 30, 31 /)     !: (leap-year) 
     
    3861      &                                           31, 31, 30, 31, 30, 31 /)     !: (365 days a year) 
    3962 
    40    !!---------------------------------------------------------------------- 
    41    !!  OPA 9.0 , LOCEAN-IPSL (2005)  
    42    !! $Id$  
    43    !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt 
     63 
     64   !!---------------------------------------------------------------------- 
     65   !!  OPA 9.0 , LOCEAN-IPSL (2006)  
     66   !! $Id$ 
     67   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    4468   !!---------------------------------------------------------------------- 
    4569 
    4670CONTAINS 
     71 
     72   SUBROUTINE day_init 
     73      !!---------------------------------------------------------------------- 
     74      !!                   ***  ROUTINE day_init  *** 
     75      !!  
     76      !! ** Purpose :   Initialization of the calendar values to their values 1 time step before nit000  
     77      !!                because day will be called at the beginning of step 
     78      !! 
     79      !! ** Action  : - nyear        : current year 
     80      !!              - nmonth       : current month of the year nyear 
     81      !!              - nday         : current day of the month nmonth 
     82      !!              - nday_year    : current day of the year nyear 
     83      !!              - rsec_year    : current time step counted in second since 00h jan 1st of the current year 
     84      !!              - rsec_month   : current time step counted in second since 00h 1st day of the current month 
     85      !!              - rsec_day     : current time step counted in second since 00h of the current day 
     86      !!              - sec1jan000   : second since Jan. 1st 00h of nit000 year and Jan. 1st 00h of the current year 
     87      !!              - nmonth_len, nyear_len, rmonth_half, rmonth_end through day_mth 
     88      !!---------------------------------------------------------------------- 
     89 
     90      ! all calendar staff is based on the fact that MOD( rday, rdttra(1) ) == 0 
     91      IF( MOD( rday, rdttra(1) ) /= 0 )   CALL ctl_stop( 'the time step must devide the number of second of in a day' ) 
     92 
     93      ! set the calandar from ndastp (read in restart file and namelist) 
     94      nyear   =   ndastp / 10000 
     95      nmonth  = ( ndastp - (nyear * 10000) ) / 100 
     96      nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 )  
     97 
     98      sec1jan000 = 0.e0 
     99      CALL day_mth 
     100       
     101      IF ( nday == 0 ) THEN     !   for ex if ndastp = ndate0 - 1 
     102         nmonth = nmonth - 1   
     103         nday = nmonth_len(nmonth) 
     104      ENDIF 
     105      IF ( nmonth == 0 ) THEN   ! go at the end of previous year 
     106         nmonth = 12 
     107         nyear = nyear - 1 
     108         sec1jan000 = sec1jan000 - rday * REAL( nyear_len(0), wp ) 
     109         IF( nleapy == 1 )   CALL day_mth 
     110      ENDIF 
     111       
     112      ! day since january 1st 
     113      nday_year = nday + SUM( nmonth_len(1:nmonth - 1) ) 
     114       
     115      ! number of seconds since the beginning of current year/month at the middle of the time-step 
     116      rsec_year  = REAL( nday_year, wp ) * rday - 0.5 * rdttra(1)   ! 1 time step before the middle of the first time step 
     117      rsec_month = REAL( nday     , wp ) * rday - 0.5 * rdttra(1)   ! because day will be called at the beginning of step 
     118      rsec_day   =                         rday - 0.5 * rdttra(1) 
     119 
     120      ! control print 
     121      IF(lwp) WRITE(numout,*)' ==============>> 1/2 time step before the start of the run DATE Y/M/D = ',   & 
     122           &                   nyear, '/', nmonth, '/', nday, '  rsec_day:', rsec_day 
     123       
     124   END SUBROUTINE day_init 
     125 
     126 
     127   SUBROUTINE day_mth 
     128      !!---------------------------------------------------------------------- 
     129      !!                   ***  ROUTINE day_init  *** 
     130      !!  
     131      !! ** Purpose :   calendar values related to the months 
     132      !! 
     133      !! ** Action  : - nmonth_len    : length in days of the months of the current year 
     134      !!              - nyear_len     : length in days of the previous/current year 
     135      !!              - rmonth_half   : second since the beginning of the year and the halft of the months 
     136      !!              - rmonth_end    : second since the beginning of the year and the end of the months 
     137      !!---------------------------------------------------------------------- 
     138      INTEGER  ::   jm               ! dummy loop indice 
     139      !!---------------------------------------------------------------------- 
     140 
     141      ! length of the month of the current year (from nleapy, read in namelist) 
     142      IF ( nleapy < 2 ) THEN  
     143         nmonth_len(:) = (/ 31, 31, 28, 31, 30, 31, 30, 31, 31, 30, 31, 30, 31, 31 /) 
     144         nyear_len(:) = 365 
     145         IF ( nleapy == 1 ) THEN   ! we are using calandar with leap years 
     146            IF ( MOD(nyear-1, 4) == 0 .AND. ( MOD(nyear-1, 400) == 0 .OR. MOD(nyear-1, 100) /= 0 ) ) THEN 
     147               nyear_len(0) = 366 
     148            ENDIF 
     149            IF ( MOD(nyear, 4) == 0 .AND. ( MOD(nyear, 400) == 0 .OR. MOD(nyear, 100) /= 0 ) ) THEN 
     150               nmonth_len(2) = 29 
     151               nyear_len(1) = 366 
     152            ENDIF 
     153         ENDIF 
     154      ELSE 
     155         nmonth_len(:) = nleapy   ! all months with nleapy days per year 
     156         nyear_len(:) = 12 * nleapy 
     157      ENDIF 
     158 
     159      ! half month in second since the begining of the year: 
     160      ! time since Jan 1st   0     1     2    ...    11    12    13 
     161      !          ---------*--|--*--|--*--| ... |--*--|--*--|--*--|-------------------------------------- 
     162      !                 <---> <---> <--->  ...  <---> <---> <--->         
     163      ! month number      0     1     2    ...    11    12    13 
     164      ! 
     165      ! rmonth_half(jm) = rday * REAL( 0.5 * nmonth_len(jm) + SUM(nmonth_len(1:jm-1)) ) 
     166      rmonth_half(0) = - 0.5 * rday * REAL( nmonth_len(0), wp ) 
     167      DO jm = 1, 13 
     168         rmonth_half(jm) = rmonth_half(jm-1) + 0.5 * rday * REAL( nmonth_len(jm-1) + nmonth_len(jm), wp ) 
     169      END DO 
     170 
     171      rmonth_end(0) = 0. 
     172      DO jm = 1, 13 
     173         rmonth_end(jm) = rmonth_end(jm-1) + rday * REAL( nmonth_len(jm), wp ) 
     174      END DO 
     175                  
     176   END SUBROUTINE  
     177 
    47178 
    48179   SUBROUTINE day( kt ) 
     
    58189      !!              - nday      : current day of the month nmonth 
    59190      !!              - nday_year : current day of the year nyear 
    60       !!              - ndastp    : =nyear*10000+nmonth*100+nday 
     191      !!              - ndastp    : = nyear*10000 + nmonth*100 + nday 
    61192      !!              - adatrj    : date in days since the beginning of the run 
    62       !! 
    63       !! History : 
    64       !!        !  94-09  (M. Pontaud M. Imbard)  Original code 
    65       !!        !  97-03  (O. Marti) 
    66       !!        !  97-05  (G. Madec)  
    67       !!        !  97-08  (M. Imbard) 
    68       !!   9.0  !  03-09  (G. Madec)  F90 + nyear, nmonth, nday 
    69       !!        !  04-01  (A.M. Treguier) new calculation based on adatrj 
     193      !!              - rsec_year : current time of the year (in second since 00h, jan 1st) 
    70194      !!----------------------------------------------------------------------       
    71       !! * Arguments 
    72       INTEGER, INTENT( in ) ::   kt      ! ocean time-step indices 
    73  
    74       !! * Local declarations 
    75       INTEGER  ::   js                   ! dummy loop indice 
    76       INTEGER  ::   iend, iday0, iday1   ! temporary integers 
    77       REAL(wp) :: zadatrjn, zadatrjb     ! adatrj at timestep kt-1 and kt-2  
    78       !!---------------------------------------------------------------------- 
    79  
    80       ! 0.  initialization of adatrj0 and nday, nmonth,nyear, nday_year. 
    81       !     ndastp has been initialized in domain.F90 or restart.F90 
    82       !----------------------------------------------------------------- 
    83  
    84       IF( kt == nit000 ) THEN 
    85  
    86          IF( .NOT.ln_rstart )   adatrj0 = 0.e0      ! adatrj0 initialized in rst_read when restart  
    87  
    88          adatrj  = adatrj0 
    89          nyear   =   ndastp / 10000 
    90          nmonth  = ( ndastp - (nyear * 10000) ) / 100 
    91          nday    =   ndastp - (nyear * 10000) - ( nmonth * 100 )  
    92  
    93          ! Calculates nday_year, day since january 1st (useful to read  daily forcing fields) 
    94          nday_year =  nday 
    95          !                               ! accumulates days of previous months of this year 
    96          DO js = 1, nmonth-1 
    97             IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN 
    98                nday_year = nday_year + nbiss(js) 
    99             ELSE 
    100                nday_year = nday_year + nobis(js) 
    101             ENDIF 
    102          END DO 
    103  
    104       ENDIF 
    105  
    106       ! I.  calculates adatrj, zadatrjn, zadatrjb. 
    107       ! ------------------------------------------------------------------ 
    108  
    109       adatrj    = adatrj0 + ( kt - nit000 + 1 ) * rdttra(1) / rday 
    110       zadatrjn  = adatrj0 + ( kt - nit000     ) * rdttra(1) / rday 
    111       zadatrjb  = adatrj0 + ( kt - nit000 - 1 ) * rdttra(1) / rday 
    112  
    113  
    114       ! II.  increment the date.  The date corresponds to 'now' variables (kt-1), 
    115       !      which is the time step of forcing fields.  
    116       !      Do not do this at nit000  unless nrstdt= 2 
    117       !      In that case ndastp (read in restart) was for step nit000-2 
    118       ! ------------------------------------------------------------------- 
    119  
    120       iday0 = INT( zadatrjb ) 
    121       iday1 = INT( zadatrjn ) 
    122  
    123       IF( iday1 - iday0 >= 1 .AND. ( kt /= nit000 .OR. nrstdt == 2 ) ) THEN 
    124  
    125          ! increase calendar 
    126          nyear  =   ndastp / 10000 
    127          nmonth = ( ndastp - (nyear * 10000) ) / 100 
    128          nday   =   ndastp - (nyear * 10000) - ( nmonth * 100 )  
    129          nday = nday + 1 
    130          IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN 
    131             iend = nbiss(nmonth) 
    132          ELSEIF( nleapy > 1 ) THEN  
    133             iend = nleapy 
    134          ELSE  
    135             iend = nobis(nmonth) 
    136          ENDIF 
    137          IF( nday == iend + 1 ) THEN 
    138             nday  = 1 
     195      INTEGER, INTENT(in) ::   kt        ! ocean time-step indices 
     196      ! 
     197      CHARACTER (len=25) ::   charout 
     198      !!---------------------------------------------------------------------- 
     199 
     200      !                                                 ! New time-step 
     201      rsec_year  = rsec_year  + rdttra(1)  
     202      rsec_month = rsec_month + rdttra(1)                  
     203      rsec_day   = rsec_day   + rdttra(1)                  
     204      adatrj = adatrj + rdttra(1) / rday 
     205       
     206      IF( rsec_day > rday ) THEN                        ! NEW day 
     207         ! 
     208         nday      = nday + 1 
     209         nday_year = nday_year + 1 
     210         rsec_day  = 0.5 * rdttra(1)                  
     211         ! 
     212         IF( nday == nmonth_len(nmonth) + 1 ) THEN      ! NEW month 
     213            nday   = 1 
    139214            nmonth = nmonth + 1 
    140             IF( nmonth == 13 ) THEN 
    141                nmonth  = 1 
    142                nyear = nyear + 1 
     215            rsec_month = 0.5 * rdttra(1) 
     216            IF( nmonth == 13 ) THEN                     ! NEW year 
     217               nyear     = nyear + 1 
     218               nmonth    = 1 
     219               nday_year = 1 
     220               rsec_year = 0.5 * rdttra(1) 
     221               sec1jan000 = sec1jan000 + rday * REAL( nyear_len(1), wp ) 
     222               IF( nleapy == 1 )   CALL day_mth 
    143223            ENDIF 
    144224         ENDIF 
    145          ndastp = nyear * 10000 + nmonth * 100 + nday 
    146  
    147          ! Calculates nday_year, day since january 1st (useful to read  daily forcing fields) 
    148          nday_year =  nday 
    149          !                                ! accumulates days of previous months of this year 
    150          DO js = 1, nmonth-1 
    151             IF( nleapy == 1 .AND. MOD( nyear, 4 ) == 0 ) THEN 
    152                nday_year = nday_year + nbiss(js) 
    153             ELSE 
    154                nday_year = nday_year + nobis(js) 
    155             ENDIF 
    156          END DO 
    157  
    158          IF(lwp) WRITE(numout,*)' ==============>> time-step =', kt, ' New day, DATE= ',   & 
    159             &                   nyear, '/', nmonth, '/', nday, 'nday_year:', nday_year 
    160       ENDIF 
    161  
     225         ! 
     226         ndastp = nyear * 10000 + nmonth * 100 + nday   ! NEW date 
     227         ! 
     228         IF(lwp) WRITE(numout,'(a,i8,a,i4.4,a,i2.2,a,i2.2,a,i3.3)') '======>> time-step =', kt,   & 
     229              &   '      New day, DATE Y/M/D = ', nyear, '/', nmonth, '/', nday, '      nday_year = ', nday_year 
     230         IF(lwp) WRITE(numout,'(a,F9.0,a,F9.0,a,F9.0)') '         rsec_year = ', rsec_year,   & 
     231              &   '   rsec_month = ', rsec_month, '   rsec_day = ', rsec_day 
     232      ENDIF 
     233       
     234      IF(ln_ctl) THEN 
     235         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear 
     236         CALL prt_ctl_info(charout) 
     237      ENDIF 
     238 
     239      ! 
    162240   END SUBROUTINE day 
    163  
    164241   !!====================================================================== 
    165242END MODULE daymod 
  • trunk/NEMO/OFF_SRC/dtadyn.F90

    r1181 r1291  
    206206         flx  ! auxiliary field for 2-D surface boundary conditions 
    207207 
    208  
    209208      ! 0. Initialization 
    210209      ! ----------------- 
    211210 
    212211      IF (lfirdyn) THEN 
    213       ! 
    214       ! time step MUST BE nint000 
    215       ! 
    216           IF (kt.ne.nit000) THEN 
    217               IF (lwp) THEN 
    218                   WRITE (numout,*) ' kt MUST BE EQUAL to nit000. kt=',kt  & 
    219                      ,' nit000=',nit000 
    220               END IF 
     212         ! first time step MUST BE nit000 
     213         IF( kt /= nit000 ) THEN 
     214            IF (lwp) THEN  
     215               WRITE (numout,*) ' kt MUST BE EQUAL to nit000. kt=',kt ,' nit000=',nit000  
    221216              STOP 'dtadyn' 
    222           END if 
    223       ! Initialize the parameters of the interpolation 
    224       CALL dta_dyn_init 
     217            ENDIF 
     218          ENDIF  
     219          ! Initialize the parameters of the interpolation 
     220          CALL dta_dyn_init 
    225221      ENDIF 
    226222 
     
    234230      zweighm1 = 1. - zweigh 
    235231 
    236       IF (lperdyn) THEN 
     232      IF( lperdyn ) THEN 
    237233         iperm1 = MOD(INT(zt),ndtadyn) 
    238234      ELSE 
     
    240236      ENDIF 
    241237      iper = iperm1 + 1 
    242       IF (iperm1 == 0) THEN 
    243           IF (lperdyn) THEN 
     238      IF( iperm1 == 0 ) THEN 
     239          IF( lperdyn ) THEN 
    244240              iperm1 = ndtadyn 
    245241          ELSE  
    246               IF (lfirdyn) THEN 
    247                   IF (lwp) THEN  
    248                       WRITE (numout,*) ' dynamic file is not periodic ' 
    249                       WRITE (numout,*) ' with or without interpolation, ' 
    250                       WRITE (numout,*) ' we take the first value' 
    251                       WRITE (numout,*) ' for the previous period ' 
    252                       WRITE (numout,*) ' iperm1 = 0  ' 
    253                   END IF  
     242              IF( lfirdyn ) THEN  
     243                  IF (lwp) WRITE (numout,*) &  
     244                      &   ' dynamic file is not periodic with or without interpolation  & 
     245                      &   we take the first value for the previous period iperm1 = 0  ' 
    254246              END IF 
    255247          END IF  
  • trunk/NEMO/OFF_SRC/opa.F90

    r1152 r1291  
    2020   USE istate          ! initial state setting          (istate_init routine) 
    2121   USE eosbn2          ! equation of state            (eos bn2 routine) 
    22    USE zpshde          ! partial step: hor. derivative (zps_hde routine) 
    2322 
    2423   ! ocean physics 
     
    130129      ENDIF 
    131130 
    132  
    133131      !                                     ! ============================== ! 
    134132      !                                     !  Model general initialization  ! 
     
    138136 
    139137                                            ! Domain decomposition 
    140       IF( jpni*jpnj == jpnij ) THEN 
     138      IF( jpni * jpnj == jpnij ) THEN 
    141139         CALL mpp_init                          ! standard cutting out 
    142140      ELSE 
     
    147145 
    148146      CALL dom_cfg                          ! Domain configuration 
    149        
     147 
    150148      CALL dom_init                         ! Domain 
    151149 
    152       CALL day( nit000 )                    ! Calendar 
     150      CALL istate_init                      ! ocean initial state (Dynamics and tracers) 
    153151 
    154       CALL istate_init                      ! ocean initial state (Dynamics and tracers) 
    155 !!add 
    156                        CALL eos( tn, sn, rhd, rhop )        ! before potential and in situ densities 
     152      CALL trc_ini                           ! Passive tracers 
    157153 
    158                        CALL bn2( tn, sn, rn2 )              ! before Brunt-Vaisala frequency 
     154      CALL day_init                          ! Calendar 
    159155 
    160       IF( ln_zps    )   CALL zps_hde( nit000, tn, sn, rhd,  &  ! Partial steps: before Horizontal DErivative 
    161                                           gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level 
    162                                           gtv, gsv, grv ) 
    163  
    164 !!add 
    165  
    166       ! Initialization for the dynamics 
    167       ! 
    168       CALL dta_dyn(nit000)      
    169  
    170 #if defined key_top 
    171       CALL trc_ini                           ! Passive tracers 
    172 #endif 
    173  
     156      CALL dta_dyn( nit000 )                 ! Initialization for the dynamics 
    174157      !                                     ! Ocean physics 
    175158      CALL tra_qsr_init                         ! Solar radiation penetration 
     
    178161      CALL ldf_tra_init                         ! Lateral ocean tracer physics 
    179162#endif  
    180  
    181       !                                     ! Ocean trends 
    182  
    183163      !                                     ! =============== ! 
    184164      !                                     !  time stepping  ! 
  • trunk/NEMO/OFF_SRC/step.F90

    r1152 r1291  
    8181      CALL dta_dyn( kstp )          ! Interpolation of the dynamical fields 
    8282 
    83 #if defined key_top 
    84       !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
    85       ! Passive Tracer Model 
    86       !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    87       ! N.B. ua, va, ta, sa arrays are used as workspace in this section 
    88       !----------------------------------------------------------------------- 
     83      CALL trc_stp( kstp, indic)           ! time-stepping 
    8984 
    90                              CALL trc_stp( kstp, indic)           ! time-stepping 
    91  
    92  
    93 #endif 
    9485 
    9586      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    9788      !<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<<< 
    9889      !                                            ! Time loop: control and print 
    99                        CALL stp_ctl( kstp ) 
     90       CALL stp_ctl( kstp ) 
    10091 
    10192 
Note: See TracChangeset for help on using the changeset viewer.