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 1287 – NEMO

Changeset 1287


Ignore:
Timestamp:
2009-02-03T14:57:43+01:00 (15 years ago)
Author:
cetlod
Message:

Initialization of PH in a better way in PISCEs model, see ticket:316

Location:
trunk/NEMO/TOP_SRC
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/TOP_SRC/PISCES/trcini_pisces.F90

    r1264 r1287  
    5353      !! 
    5454      !! ** Purpose :   Initialisation of the PISCES biochemical model 
    55       !!---------------------------------------------------------------------- 
    56       INTEGER ::   ji, jj, jk 
    57       REAL(wp) ::  caralk, bicarb, co3 
    58  
    59  
    6055      !!---------------------------------------------------------------------- 
    6156 
     
    122117         trn(:,:,:,jpnh4) = bioma0 
    123118 
    124          ! Initialization of chemical variables of the carbon cycle 
    125          ! -------------------------------------------------------- 
    126          DO jk = 1, jpk 
    127             DO jj = 1, jpj 
    128                DO ji = 1, jpi 
    129                   caralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  ) 
    130                   co3    = ( caralk - trn(ji,jj,jk,jpdic) ) *        tmask(ji,jj,jk)   & 
    131                      &   +                  0.5e-3          * ( 1. - tmask(ji,jj,jk) ) 
    132                   bicarb = ( 2. * trn(ji,jj,jk,jpdic) - caralk ) 
    133                   hi(ji,jj,jk) = ( ak23(ji,jj,jk) * bicarb / co3 ) *        tmask(ji,jj,jk)   & 
    134                      &         +            1.e-9                  * ( 1. - tmask(ji,jj,jk) ) 
    135                END DO 
    136             END DO 
    137          END DO 
    138           
     119         ! initialize the half saturation constant for silicate 
     120         ! ---------------------------------------------------- 
     121         xksi(:,:)    = 2.e-6 
     122         xksimax(:,:) = xksi(:,:) 
     123 
    139124      ENDIF 
    140  
    141  
    142  
    143       ! initialize the half saturation constant for silicate 
    144       ! ---------------------------------------------------- 
    145       xksi(:,:)    = 2.e-6 
    146       xksimax(:,:) = xksi(:,:) 
    147125 
    148126      IF(lwp) WRITE(numout,*) 'Initialization of PISCES tracers done' 
  • trunk/NEMO/TOP_SRC/PISCES/trcsms_pisces.F90

    r1255 r1287  
    6161      !!--------------------------------------------------------------------- 
    6262 
     63      IF( kt == nittrc000  .AND. .NOT. lrsttr )   CALL trc_sms_pisces_init    ! Initialization (first time-step only) 
     64 
    6365      IF( ndayflxtr /= nday ) THEN      ! New days 
    6466         ! 
     
    8385      CALL p4z_flx( kt )             ! Compute surface fluxes 
    8486 
    85  
    8687      DO jn = jp_pcs0, jp_pcs1 
    8788        CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. ) 
     
    9798      END IF 
    9899 
    99 #if defined key_sed 
     100      IF( lk_sed ) THEN  
     101         ! 
     102         CALL sed_model( kt )     !  Main program of Sediment model 
     103         ! 
     104         DO jn = jp_pcs0, jp_pcs1 
     105           CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. ) 
     106         END DO 
     107         ! 
     108      ENDIF 
    100109 
    101       CALL sed_model( kt )     !  Main program of Sediment model 
     110   END SUBROUTINE trc_sms_pisces 
    102111 
    103       DO jn = jp_pcs0, jp_pcs1 
    104         CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. ) 
     112   SUBROUTINE trc_sms_pisces_init 
     113      !!---------------------------------------------------------------------- 
     114      !!                  ***  ROUTINE trc_sms_pisces_init  *** 
     115      !! 
     116      !! ** Purpose :   Initialization of PH variable 
     117      !! 
     118      !!---------------------------------------------------------------------- 
     119      INTEGER  ::  ji, jj, jk 
     120      REAL(wp) ::  zcaralk, zbicarb, zco3 
     121      REAL(wp) ::  ztmas, ztmas1 
     122 
     123      ! Initialization of chemical variables of the carbon cycle 
     124      ! -------------------------------------------------------- 
     125      DO jk = 1, jpk 
     126         DO jj = 1, jpj 
     127            DO ji = 1, jpi 
     128               ztmas   = tmask(ji,jj,jk) 
     129               ztmas1  = 1. - tmask(ji,jj,jk) 
     130               zcaralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  ) 
     131               zco3    = ( zcaralk - trn(ji,jj,jk,jpdic) ) * ztmas + 0.5e-3 * ztmas1 
     132               zbicarb = ( 2. * trn(ji,jj,jk,jpdic) - zcaralk ) 
     133               hi(ji,jj,jk) = ( ak23(ji,jj,jk) * zbicarb / zco3 ) * ztmas + 1.e-9 * ztmas1 
     134            END DO 
     135         END DO 
    105136      END DO 
    106137 
    107 #endif 
    108  
    109       ! 
    110    END SUBROUTINE trc_sms_pisces 
     138   END SUBROUTINE trc_sms_pisces_init 
    111139 
    112140#else 
  • trunk/NEMO/TOP_SRC/trcrst.F90

    r1254 r1287  
    2424   USE lib_mpp 
    2525   USE iom 
     26   USE daymod 
    2627    
    2728   IMPLICIT NONE 
     
    8990      !! ** purpose  :   read passive tracer fields in restart files 
    9091      !!---------------------------------------------------------------------- 
    91       INTEGER  ::   jn   
    92       INTEGER  ::   iarak0 
    93       REAL(wp) ::   zkt, zarak0 
     92      INTEGER  ::  jn   
     93      INTEGER  ::  iarak0 
     94      REAL(wp) ::  zarak0 
     95#if defined key_pisces  
     96      INTEGER  ::  ji, jj, jk 
     97      REAL(wp) ::  zcaralk, zbicarb, zco3 
     98      REAL(wp) ::  ztmas, ztmas1 
     99#endif 
     100 
    94101      !!---------------------------------------------------------------------- 
    95102 
     
    98105      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~' 
    99106 
     107      CALL iom_open( cn_trcrst_in, numrtr, kiolib = jprstlib ) 
     108 
     109      ! Time domain : restart 
     110      ! --------------------- 
     111      CALL trc_rst_cal( nittrc000, 'READ' )   ! calendar 
     112 
    100113      IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN   ;   iarak0 = 1 
    101114      ELSE                                           ;   iarak0 = 0 
    102115      ENDIF 
    103  
    104       IF(lwp) WRITE(numout,*) 
    105       IF(lwp) WRITE(numout,*) '   the present run starts at the time step nit000 = ', nit000 
    106       IF(lwp .AND. iarak0 == 1 )   WRITE(numout,*) '   and needs previous fields for Arakawa sheme ??? ' 
    107  
    108  
    109       ! Time domain : restart 
    110       ! ------------------------- 
    111       IF(lwp) WRITE(numout,*) 
    112       IF(lwp) WRITE(numout,*) ' *** passive tracer restart option' 
    113       SELECT CASE ( nrsttr ) 
    114       CASE ( 0 ) 
    115          IF(lwp) WRITE(numout,*) '    nrsttr = 0 no control of nit000' 
    116       CASE ( 1 ) 
    117          IF(lwp) WRITE(numout,*) '    nrsttr = 1 we control the date of nit000' 
    118       CASE ( 2 ) 
    119          IF(lwp) WRITE(numout,*) '    nrsttr = 2 the date adatrj is read in restart file' 
    120       CASE DEFAULT 
    121          IF(lwp) WRITE(numout,*) '  ===>>>> nrsttr not equal 0, 1 or 2 : no control of the date' 
    122          IF(lwp) WRITE(numout,*) '  =======                  =========' 
    123       END SELECT 
    124  
    125       CALL iom_open( cn_trcrst_in, numrtr, kiolib = jprstlib ) 
    126  
    127       CALL iom_get( numrtr, 'kt'   , zkt    ) 
    128116      CALL iom_get( numrtr, 'arak0', zarak0 ) 
    129  
    130       IF(lwp) WRITE(numout,*) 
    131       IF(lwp) WRITE(numout,*) ' Info on the restart file read : ' 
    132       IF(lwp) WRITE(numout,*) '    time-step           : ', NINT( zkt    ) 
    133       IF(lwp) WRITE(numout,*) '    arakawa option      : ', NINT( zarak0 ) 
    134  
    135  
    136       IF( nittrc000 - NINT( zkt ) /= 1 .AND. nrsttr /= 0 )  &      ! control of date 
    137          &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart', & 
    138          &                  ' verify the restart file or rerun with nrstdt = 0 (namelist)' ) 
    139117 
    140118      IF( iarak0 /= NINT( zarak0 ) )   &                           ! Control of the scheme 
     
    142120         & ' it must be the same type for both restart and previous run', & 
    143121         & ' centered or euler '  ) 
     122      IF(lwp) WRITE(numout,*) 
     123 
     124      IF(lwp) WRITE(numout,*) '    arakawa option      : ', NINT( zarak0 ) 
    144125 
    145126 
     
    149130      END DO 
    150131 
    151      DO jn = 1, jptra 
     132      DO jn = 1, jptra 
    152133         CALL iom_get( numrtr, jpdom_autoglo, 'TRB'//ctrcnm(jn), trb(:,:,:,jn) )  
    153134      END DO 
     
    157138      CALL iom_get( numrtr, jpdom_autoglo, 'SEDN'//ctrcnm(jpdet), sedpocn(:,:) )  
    158139#endif 
    159  
    160140#if defined key_pisces 
     141      ! 
     142      IF( ln_pisdmp ) CALL pis_dmp_ini  ! relaxation of some tracers 
     143      ! 
     144      IF( iom_varid( numrtr, 'PH', ldstop = .FALSE. ) > 0 ) THEN 
     145         CALL iom_get( numrtr, jpdom_autoglo, 'PH' , hi(:,:,:)  ) 
     146      ELSE 
     147         ! Set PH from  total alkalinity, borat (???), akb3 (???) and ak23 (???) 
     148         ! -------------------------------------------------------- 
     149         DO jk = 1, jpk 
     150            DO jj = 1, jpj 
     151               DO ji = 1, jpi 
     152                  ztmas   = tmask(ji,jj,jk) 
     153                  ztmas1  = 1. - tmask(ji,jj,jk) 
     154                  zcaralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / (  1. + 1.E-8 / ( rtrn + akb3(ji,jj,jk) )  ) 
     155                  zco3    = ( zcaralk - trn(ji,jj,jk,jpdic) ) * ztmas + 0.5e-3 * ztmas1 
     156                  zbicarb = ( 2. * trn(ji,jj,jk,jpdic) - zcaralk ) 
     157!!                  write(numout,*) 'plante :',ji,jj,jk,ztmas,ztmas1,ak23(ji,jj,jk),zbicarb ,zco3 
     158                  hi(ji,jj,jk) = ( ak23(ji,jj,jk) * zbicarb / zco3 ) * ztmas + 1.e-9 * ztmas1 
     159               END DO 
     160            END DO 
     161         END DO 
     162      ENDIF 
    161163      CALL iom_get( numrtr, jpdom_autoglo, 'Silicalim', xksi(:,:) )  
    162       CALL iom_get( numrtr, jpdom_autoglo, 'Silicamax', xksimax(:,:) ) 
    163       CALL trc_rst_ini  ! Initialisation of some variables 
    164 #endif 
    165  
     164      IF( iom_varid( numrtr, 'Silicamax', ldstop = .FALSE. ) > 0 ) THEN 
     165         CALL iom_get( numrtr, jpdom_autoglo, 'Silicamax' , xksimax(:,:)  ) 
     166      ELSE 
     167         xksimax(:,:) = xksi(:,:) 
     168      ENDIF 
     169#endif 
    166170#if defined key_cfc 
    167171      DO jn = jp_cfc0, jp_cfc1 
     
    169173      END DO 
    170174#endif 
    171  
    172175#if defined key_c14b 
    173176      CALL iom_get( numrtr, jpdom_autoglo, 'qint_'//ctrcnm(jn) , qint_c14(:,:) )  
    174177#endif 
    175  
    176178#if defined key_my_trc 
    177179#endif 
    178  
    179  
     180       
    180181      CALL iom_close( numrtr ) 
    181182      ! 
     
    191192      INTEGER, INTENT( in ) ::   kt    ! ocean time-step index 
    192193      !! 
    193       INTEGER  :: ji, jj, jk, jn 
    194       !!---------------------------------------------------------------------- 
    195  
    196       IF(  kt == nitrst ) THEN 
    197          IF(lwp) WRITE(numout,*) 
    198          IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp 
    199          IF(lwp) WRITE(numout,*) '~~~~~~~' 
    200       ENDIF 
    201  
    202       CALL iom_rstput( kt, nitrst, numrtw, 'kt'   ,  REAL( kt, wp )  ) 
    203       IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN 
    204          CALL iom_rstput( kt, nitrst, numrtw, 'arak0', 1. ) 
    205       ELSE 
    206          CALL iom_rstput( kt, nitrst, numrtw, 'arak0', 0. ) 
    207       ENDIF 
    208  
    209  
    210          ! prognostic variables 
    211          ! -------------------- 
     194      INTEGER  :: jn 
     195      REAL(wp) :: zarak0 
     196      !!---------------------------------------------------------------------- 
     197 
     198 
     199      CALL trc_rst_cal( kt, 'WRITE' )   ! calendar 
     200 
     201      IF( ln_trcadv_cen2 .OR. ln_trcadv_tvd ) THEN   ;   zarak0 = 1. 
     202      ELSE                                           ;   zarak0 = 0. 
     203      ENDIF 
     204      CALL iom_rstput( kt, nitrst, numrtw, 'arak0', zarak0 ) 
     205 
     206      ! prognostic variables 
     207      ! -------------------- 
    212208      DO jn = 1, jptra 
    213209         CALL iom_rstput( kt, nitrst, numrtw, 'TRN'//ctrcnm(jn), trn(:,:,:,jn) ) 
     
    219215 
    220216#if defined key_lobster 
    221       CALL iom_rstput( kt, nitrst, numrtw, 'SEDB'//ctrcnm(jpdet), sedpocb(:,:) ) 
    222       CALL iom_rstput( kt, nitrst, numrtw, 'SEDN'//ctrcnm(jpdet), sedpocn(:,:) ) 
    223 #endif 
    224  
    225 #if defined key_pisces 
    226       CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:) ) 
    227       CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:) ) 
    228 #endif 
    229  
     217         CALL iom_rstput( kt, nitrst, numrtw, 'SEDB'//ctrcnm(jpdet), sedpocb(:,:) ) 
     218         CALL iom_rstput( kt, nitrst, numrtw, 'SEDN'//ctrcnm(jpdet), sedpocn(:,:) ) 
     219#endif 
     220#if defined key_pisces  
     221         CALL iom_rstput( kt, nitrst, numrtw, 'PH', hi(:,:,:) ) 
     222         CALL iom_rstput( kt, nitrst, numrtw, 'Silicalim', xksi(:,:) ) 
     223         CALL iom_rstput( kt, nitrst, numrtw, 'Silicamax', xksimax(:,:) ) 
     224#endif 
    230225#if defined key_cfc 
    231       DO jn = jp_cfc0, jp_cfc1 
    232          CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jn) ) 
    233       END DO 
    234 #endif 
    235  
     226         DO jn = jp_cfc0, jp_cfc1 
     227            CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_cfc(:,:,jn) ) 
     228         END DO 
     229#endif 
    236230#if defined key_c14b 
    237       CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_c14(:,:) ) 
    238 #endif 
    239  
     231         CALL iom_rstput( kt, nitrst, numrtw, 'qint_'//ctrcnm(jn), qint_c14(:,:) ) 
     232#endif 
    240233#if defined key_my_trc 
    241234#endif 
    242  
    243  
    244        IF( kt == nitrst ) THEN 
     235       
     236      IF( kt == nitrst ) THEN 
    245237          CALL trc_rst_stat            ! statistics 
    246238          CALL iom_close( numrtw )     ! close the restart file (only at last time step) 
     
    248240          lrst_trc = .FALSE. 
    249241#endif 
    250        ENDIF 
     242      ENDIF 
    251243      ! 
    252244   END SUBROUTINE trc_rst_wri 
    253245 
     246   SUBROUTINE trc_rst_cal( kt, cdrw ) 
     247      !!--------------------------------------------------------------------- 
     248      !!                   ***  ROUTINE trc_rst_cal  *** 
     249      !! 
     250      !!  ** Purpose : Read or write calendar in restart file: 
     251      !! 
     252      !!  WRITE(READ) mode: 
     253      !!       kt        : number of time step since the begining of the experiment at the 
     254      !!                   end of the current(previous) run 
     255      !!       adatrj(0) : number of elapsed days since the begining of the experiment at the 
     256      !!                   end of the current(previous) run (REAL -> keep fractions of day) 
     257      !!       ndastp    : date at the end of the current(previous) run (coded as yyyymmdd integer) 
     258      !! 
     259      !!   According to namelist parameter nrstdt, 
     260      !!       nrsttr = 0  no control on the date (nittrc000 is  arbitrary). 
     261      !!       nrsttr = 1  we verify that nit000 is equal to the last 
     262      !!                   time step of previous run + 1. 
     263      !!       In both those options, the  exact duration of the experiment 
     264      !!       since the beginning (cumulated duration of all previous restart runs) 
     265      !!       is not stored in the restart and is assumed to be (nit000-1)*rdt. 
     266      !!       This is valid is the time step has remained constant. 
     267      !! 
     268      !!       nrsttr = 2  the duration of the experiment in days (adatrj) 
     269      !!                    has been stored in the restart file. 
     270      !!---------------------------------------------------------------------- 
     271      INTEGER         , INTENT(in) ::   kt         ! ocean time-step 
     272      CHARACTER(len=*), INTENT(in) ::   cdrw       ! "READ"/"WRITE" flag 
     273      ! 
     274      REAL(wp) ::  zkt 
     275#if defined key_off_tra 
     276      REAL(wp) ::  zndastp 
     277#endif 
     278 
     279      ! Time domain : restart 
     280      ! --------------------- 
     281 
     282      IF( TRIM(cdrw) == 'READ' ) THEN 
     283         CALL iom_get ( numrtr, 'kt', zkt )   ! last time-step of previous run 
     284         IF(lwp) THEN 
     285            WRITE(numout,*) ' *** Info read in restart : ' 
     286            WRITE(numout,*) '   previous time-step                               : ', NINT( zkt ) 
     287            WRITE(numout,*) ' *** restart option' 
     288            SELECT CASE ( nrsttr ) 
     289            CASE ( 0 )   ;   WRITE(numout,*) ' nrsttr = 0 : no control of nittrc000' 
     290            CASE ( 1 )   ;   WRITE(numout,*) ' nrsttr = 1 : no control the date at nit000 (use ndate0 read in the namelist)' 
     291            CASE ( 2 )   ;   WRITE(numout,*) ' nrsttr = 2 : calendar parameters read in restart' 
     292            END SELECT 
     293            WRITE(numout,*) 
     294         ENDIF 
     295         ! Control of date  
     296         IF( nittrc000  - NINT( zkt ) /= 1 .AND.  nrsttr /= 0 )                                  & 
     297            &   CALL ctl_stop( ' ===>>>> : problem with nit000 for the restart',                 & 
     298            &                  ' verify the restart file or rerun with nrsttr = 0 (namelist)' ) 
     299#if defined key_off_tra 
     300         ! define ndastp and adatrj 
     301         IF ( nrsttr == 2 ) THEN 
     302            CALL iom_get( numrtr, 'ndastp', zndastp )  
     303            ndastp = NINT( zndastp ) 
     304            CALL iom_get( numrtr, 'adatrj', adatrj  ) 
     305         ELSE 
     306            ndastp = ndate0 - 1     ! ndate0 read in the namelist in dom_nam 
     307            adatrj = ( REAL( nittrc000-1, wp ) * rdttra(1) ) / rday 
     308            ! note this is wrong if time step has changed during run 
     309         ENDIF 
     310         ! 
     311         IF(lwp) THEN 
     312           WRITE(numout,*) ' *** Info used values : ' 
     313           WRITE(numout,*) '   date ndastp                                      : ', ndastp 
     314           WRITE(numout,*) '   number of elapsed days since the begining of run : ', adatrj 
     315           WRITE(numout,*) 
     316         ENDIF 
     317#endif 
     318 
     319      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN 
     320         ! 
     321         IF(  kt == nitrst ) THEN 
     322            IF(lwp) WRITE(numout,*) 
     323            IF(lwp) WRITE(numout,*) 'trc_wri : write the TOP restart file (NetCDF) at it= ', kt, ' date= ', ndastp 
     324            IF(lwp) WRITE(numout,*) '~~~~~~~' 
     325         ENDIF 
     326         ! calendar control 
     327         CALL iom_rstput( kt, nitrst, numrtw, 'kt'     , REAL( kt    , wp) )   ! time-step 
     328         CALL iom_rstput( kt, nitrst, numrtw, 'ndastp' , REAL( ndastp, wp) )   ! date 
     329         CALL iom_rstput( kt, nitrst, numrtw, 'adatrj' , adatrj            )   ! number of elapsed days since 
     330         !                                                                     ! the begining of the run [s] 
     331      ENDIF 
     332 
     333   END SUBROUTINE trc_rst_cal 
     334 
    254335# if defined key_pisces  
    255336 
    256    SUBROUTINE trc_rst_ini  
    257       !!---------------------------------------------------------------------- 
    258       !!                    ***  trc_rst_ini  *** 
    259       !! 
    260       !! ** purpose  : Initialisation of some variables ( hi 
    261       !!---------------------------------------------------------------------- 
    262       INTEGER  :: ji, jj, jk, jn   
     337   SUBROUTINE pis_dmp_ini  
     338      !!---------------------------------------------------------------------- 
     339      !!                    ***  pis_dmp_ini  *** 
     340      !! 
     341      !! ** purpose  : Relaxation of some tracers 
     342      !!---------------------------------------------------------------------- 
     343      INTEGER  :: ji, jj, jk   
    263344      REAL(wp) ::  & 
    264345         alkmean = 2426. ,  & ! mean value of alkalinity ( Glodap ; for Goyet 2391. ) 
     
    268349       
    269350      REAL(wp) ::   zvol, ztrasum 
    270       REAL(wp) ::   caralk, bicarb, co3 
     351 
    271352 
    272353      IF(lwp)  WRITE(numout,*) 
     
    360441!     trn(:,:,:,jpnum) = trn(:,:,:,jppoc) / ( 6. * xkr_massp ) 
    361442!#endif 
    362       !!  Set hi (???) from  total alcalinity, borat (???), akb3 (???) and ak23 (???) 
    363       !!  --------------------------------------------------------------------- 
    364       DO jk = 1, jpk 
    365          DO jj = 1, jpj 
    366             DO ji = 1,jpi 
    367                caralk = trn(ji,jj,jk,jptal) - borat(ji,jj,jk) / ( 1. + 1.e-8 / ( rtrn + akb3(ji,jj,jk) ) ) 
    368                co3    = ( caralk - trn(ji,jj,jk,jpdic) ) *       tmask(ji,jj,jk)   & 
    369                   &   +             0.5e-3               * ( 1.- tmask(ji,jj,jk) ) 
    370                bicarb = 2.* trn(ji,jj,jk,jpdic) - caralk 
    371                hi(ji,jj,jk) = ( ak23(ji,jj,jk) * bicarb / co3 )   *       tmask(ji,jj,jk)   & 
    372                   &         +             1.0e-9                  * ( 1.- tmask(ji,jj,jk) ) 
    373             END DO 
    374          END DO 
    375       END DO 
    376  
    377    END SUBROUTINE trc_rst_ini 
     443 
     444   END SUBROUTINE pis_dmp_ini 
    378445 
    379446#endif 
     
    404471         zdiag_varmin = 0.e0 
    405472         zdiag_varmax = 0.e0 
    406          DO ji = 1, jpi 
     473         DO jk = 1, jpk 
    407474            DO jj = 1, jpj 
    408                DO jk = 1,jpk 
     475               DO ji = 1, jpi 
    409476                  zvol = cvol(ji,jj,jk) 
    410477#  if defined key_off_degrad 
Note: See TracChangeset for help on using the changeset viewer.