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

Changeset 1830


Ignore:
Timestamp:
2010-04-12T15:03:51+02:00 (14 years ago)
Author:
cetlod
Message:

Computation of additional diagnostics for PISCES model ( under CPP key key_diaar5 )

  • needed for AR5 outputs (vertical inventories, passive tracers at surface,... )
  • new output file with suffix dbio_T
Location:
branches/CMIP5_IPSL/NEMO
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • branches/CMIP5_IPSL/NEMO/OFF_SRC/IOM/iom.F90

    r1749 r1830  
    986986      !! 
    987987      !!---------------------------------------------------------------------- 
    988       CHARACTER(len=6),DIMENSION( 8) ::   clsuff                   ! suffix name 
     988      CHARACTER(len=6),DIMENSION( 9) ::   clsuff                   ! suffix name 
    989989      CHARACTER(len=1),DIMENSION( 3) ::   clgrd                    ! suffix name 
    990990      CHARACTER(len=50)              ::   clname                   ! file name 
     
    10131013       
    10141014      ! output file names (attribut: name) 
    1015       clsuff(:) = (/ 'grid_T', 'grid_U', 'grid_V', 'grid_W', 'icemod', 'ptrc_T', 'diad_T', 'scalar' /)       
     1015      clsuff(:) = (/ 'grid_T', 'grid_U', 'grid_V', 'grid_W', 'icemod', 'ptrc_T', 'diad_T', 'dbio_T', 'scalar' /)       
    10161016      DO jg = 1, SIZE(clsuff)                                                                  ! grid type 
    10171017         DO jh = 1, 12                                                                         ! 1, 2, 3, 4, 6, 12 hours 
  • branches/CMIP5_IPSL/NEMO/OPA_SRC/IOM/iom.F90

    r1743 r1830  
    987987      !! 
    988988      !!---------------------------------------------------------------------- 
    989       CHARACTER(len=6),DIMENSION( 8) ::   clsuff                   ! suffix name 
     989      CHARACTER(len=6),DIMENSION( 9) ::   clsuff                   ! suffix name 
    990990      CHARACTER(len=1),DIMENSION( 3) ::   clgrd                    ! suffix name 
    991991      CHARACTER(len=50)              ::   clname                   ! file name 
     
    10151015       
    10161016      ! output file names (attribut: name) 
    1017       clsuff(:) = (/ 'grid_T', 'grid_U', 'grid_V', 'grid_W', 'icemod', 'ptrc_T', 'diad_T', 'scalar' /)       
     1017      clsuff(:) = (/ 'grid_T', 'grid_U', 'grid_V', 'grid_W', 'icemod', 'ptrc_T', 'diad_T', 'dbio_T', 'scalar' /)       
    10181018      DO jg = 1, SIZE(clsuff)                                                                  ! grid type 
    10191019         DO jh = 1, 12                                                                         ! 1, 2, 3, 4, 6, 12 hours 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zflx.F90

    r1808 r1830  
    204204          CALL mpp_sum( t_oce_co2_flx )   ! sum over the global domain 
    205205        ENDIF 
     206        ! Conversion in GtC/yr ; negative for outgoing from ocean 
     207        t_oce_co2_flx = (-1.) * t_oce_co2_flx  * 12. / 1.e15 
     208        ! 
    206209        WRITE(numout,*) ' Atmospheric pCO2    :' 
    207210        WRITE(numout,*) '-------------------- : ',kt,'  ',t_atm_co2_flx 
    208211        WRITE(numout,*) '(ppm)' 
    209         WRITE(numout,*) 'Total Flux of Carbon :' 
    210         WRITE(numout,*) '-------------------- : ',t_oce_co2_flx * 12. / 1e15 
    211         WRITE(numout,*) '(GtC/an)' 
     212        WRITE(numout,*) 'Total Flux of Carbon out of the ocean :' 
     213        WRITE(numout,*) '-------------------- : ',t_oce_co2_flx 
     214        WRITE(numout,*) '(GtC/yr)' 
    212215        t_atm_co2_flx = 0. 
    213216        t_oce_co2_flx = 0. 
     217# if defined key_iomput 
     218        CALL iom_put( "tatpco2" , t_atm_co2_flx  ) 
     219        CALL iom_put( "tco2flx" , t_oce_co2_flx  ) 
     220#endif 
    214221      ENDIF 
    215222#endif 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zlys.F90

    r1735 r1830  
    6767#if defined key_trc_dia3d && defined key_iomput 
    6868      REAL(wp) ::   zrfact2 
    69       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zcaldiss, zw3d 
     69      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zcaldiss 
    7070#endif 
    7171      CHARACTER (len=25) :: charout 
     
    9494                  ! SET DUMMY VARIABLE FOR TOTAL BORATE 
    9595                  zbot  = borat(ji,jj,jk) 
     96 
     97                  ! SET DUMMY VARIABLE FOR TOTAL BORATE 
     98                  zbot  = borat(ji,jj,jk) 
    9699                  zfact = rhop (ji,jj,jk) / 1000. + rtrn 
    97100 
     
    171174#  else 
    172175      zrfact2 = 1.e3 * rfact2r 
    173       zw3d(:,:,:) = hi  (:,:,:)                    * tmask(:,:,:) 
    174       CALL iom_put( "PH", zw3d ) 
    175       zw3d(:,:,:) = zco3(:,:,:)                    * tmask(:,:,:) 
    176       CALL iom_put( "CO3", zw3d ) 
    177       zw3d(:,:,:) = aksp(:,:,:) / calcon           * tmask(:,:,:) 
    178       CALL iom_put( "CO3sat", zw3d ) 
    179       zw3d(:,:,:) = zcaldiss(:,:,:) * zrfact2 * tmask(:,:,:) 
    180       CALL iom_put( "Dcal", zw3d ) 
     176      CALL iom_put( "PH"    , hi      (:,:,:)           * tmask(:,:,:) ) 
     177      CALL iom_put( "CO3"   , zco3    (:,:,:)           * tmask(:,:,:) ) 
     178      CALL iom_put( "CO3sat", aksp    (:,:,:) / calcon  * tmask(:,:,:) ) 
     179      CALL iom_put( "DCAL"  , zcaldiss(:,:,:) * zrfact2 * tmask(:,:,:) ) 
     180#if defined key_diaar5 
     181      CALL iom_put( "PHSFC" , hi     (:,:,1)           * tmask(:,:,1) ) 
     182#endif 
    181183#  endif 
    182184# endif 
     
    232234   END SUBROUTINE p4z_lys 
    233235#endif  
    234  
    235236   !!====================================================================== 
    236237END MODULE  p4zlys 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zmeso.F90

    r1808 r1830  
    7676#if defined key_trc_diaadd && defined key_trc_dia3d && defined key_iomput 
    7777      REAL(wp) :: zrfact2 
    78       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d 
     78#if defined key_diaar5 
     79      REAL(wp), DIMENSION(jpi,jpj) ::   zpcalint 
     80#endif 
    7981#endif 
    8082 
     
    203205      END DO 
    204206       
     207#if defined key_trc_dia3d 
     208      ! Total grazing ( grazing by microzoo is already computed in p4zmicro )  
     209      grazing(:,:,:) = grazing(:,:,:) + (  zgrazd  (:,:,:) + zgrazz  (:,:,:) + zgrazn(:,:,:) & 
     210                     &                   + zgrazpoc(:,:,:) + zgrazffe(:,:,:)  ) 
     211#endif 
     212 
    205213 
    206214      DO jk = 1,jpkm1 
     
    311319#if defined key_trc_diaadd && defined key_trc_dia3d && defined key_iomput 
    312320      zrfact2 = 1.e3 * rfact2r 
    313       zw3d(:,:,:) = (     zgrazd(:,:,:) +   zgrazz(:,:,:) + zgrazn(:,:,:) & 
    314                     & + zgrazpoc(:,:,:) + zgrazffe(:,:,:)                 ) * zrfact2 * tmask(:,:,:) 
    315       IF( jnt == nrdttrc ) CALL iom_put( "Graz2" , zw3d ) 
    316  
    317       zw3d(:,:,:) = prodcal(:,:,:) * zrfact2 * tmask(:,:,:) 
    318       IF( jnt == nrdttrc ) CALL iom_put( "Pcal"  , zw3d ) 
     321      ! Total grazing of phyto by zoo 
     322      grazing(:,:,:) = grazing(:,:,:) * zrfact2 * tmask(:,:,:) 
     323      ! Calcite production 
     324      prodcal(:,:,:) = prodcal(:,:,:) * zrfact2 * tmask(:,:,:) 
     325      IF( jnt == nrdttrc ) then  
     326         CALL iom_put( "GRAZ" , grazing  )  ! Total grazing of phyto by zooplankton 
     327         CALL iom_put( "PCAL" , prodcal  )  ! Calcite production 
     328      ENDIF 
     329#if defined key_diaar5 
     330      ! Vertically integrated calcite production 
     331      zpcalint(:,:) = 0. 
     332      DO jk = 1, jpkm1 
     333         zpcalint(:,:) = zpcalint(:,:) + prodcal(:,:,jk) * fse3t(:,:,jk) 
     334      ENDDO 
     335      IF( jnt == nrdttrc ) CALL iom_put( "INTPCAL", zpcalint )  ! Vertically integrated calcite production 
     336#endif 
    319337#endif 
    320338 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zmicro.F90

    r1808 r1830  
    7070      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zgrazmf, zgrazsf, zgrazpf 
    7171      CHARACTER (len=25) :: charout 
    72 #if defined key_trc_diaadd && defined key_trc_dia3d && defined key_iomput 
    73       REAL(wp) :: zrfact2 
    74       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d 
    75 #endif 
    7672 
    7773      !!--------------------------------------------------------------------- 
     
    8884      zgrazpf(:,:,:) = 0. 
    8985 
     86#if defined key_trc_dia3d 
     87      grazing(:,:,:) = 0.  !: Initialisation of  grazing 
     88#endif 
    9089 
    9190      zstep = rfact2 / rday      ! Time step duration for biology 
     
    156155      END DO 
    157156       
     157#if defined key_trc_dia3d 
     158      ! Grazing by microzooplankton 
     159      grazing(:,:,:) = grazing(:,:,:) + zgrazp(:,:,:) + zgrazm(:,:,:) + zgrazsd(:,:,:)  
     160#endif 
    158161 
    159162      DO jk = 1,jpkm1 
     
    231234      END DO 
    232235      ! 
    233 #if defined key_trc_diaadd && defined key_trc_dia3d && defined key_iomput 
    234       zrfact2 = 1.e3 * rfact2r 
    235       zw3d(:,:,:) = ( zgrazp(:,:,:) + zgrazm(:,:,:) + zgrazsd(:,:,:) ) * zrfact2 * tmask(:,:,:) 
    236       IF( jnt == nrdttrc ) CALL iom_put( "Graz" , zw3d ) 
    237 #endif 
    238  
    239        IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
     236      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
    240237         WRITE(charout, FMT="('micro')") 
    241238         CALL prt_ctl_trc_info(charout) 
    242239         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    243        ENDIF 
     240      ENDIF 
    244241 
    245242   END SUBROUTINE p4z_micro 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zopt.F90

    r1808 r1830  
    6161      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zekg, zekr, zekb 
    6262      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ze1 , ze2 , ze3, ze0 
    63 #if defined key_trc_diaadd && defined key_iomput 
    64      REAL(wp), DIMENSION(jpi,jpj)      ::   zw2d 
    65      REAL(wp), DIMENSION(jpi,jpj,jpk)  ::   zw3d 
    66 #endif 
    6763      !!--------------------------------------------------------------------- 
    6864 
     
    238234# else 
    239235      ! write diagnostics  
    240       zw2d(:,:  ) =  heup(:,:  ) * tmask(:,:,1) 
    241       zw3d(:,:,:) =  etot(:,:,:) * tmask(:,:,:) 
    242       IF( jnt == nrdttrc ) CALL iom_put( "Heup", zw2d )                
    243       IF( jnt == nrdttrc ) CALL iom_put( "PAR" , zw3d ) 
     236      IF( jnt == nrdttrc ) then  
     237         CALL iom_put( "Heup", heup(:,:  ) * tmask(:,:,1) )  ! euphotic layer deptht 
     238         CALL iom_put( "PAR" , etot(:,:,:) * tmask(:,:,:) )  ! Photosynthetically Available Radiation 
     239      ENDIF 
    244240# endif 
    245241#endif 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zprod.F90

    r1808 r1830  
    8181#if defined key_trc_diaadd && defined key_trc_dia3d 
    8282      REAL(wp) ::   zrfact2 
    83 #if  defined key_iomput 
    84       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d 
     83#if defined key_iomput && defined key_diaar5 
     84      REAL(wp), DIMENSION(jpi,jpj) ::   zw2d 
    8585#endif 
    8686#endif 
     
    352352        WRITE(numout,*) 'Total PP :' 
    353353        WRITE(numout,*) '-------------------- : ',tpp * 12. / 1.E12 
    354         WRITE(numout,*) '(GtC/an)' 
     354        WRITE(numout,*) '(GtC/yr)' 
    355355        tpp = 0. 
    356356      ENDIF 
    357357 
    358 #if defined key_trc_diaadd && defined key_trc_dia3d 
     358#if defined key_trc_diaadd && defined key_trc_dia3d && ! defined key_iomput 
     359      !   Supplementary diagnostics 
    359360      zrfact2 = 1.e3 * rfact2r 
    360       !   Supplementary diagnostics 
    361 #  if ! defined key_iomput 
    362361      trc3d(:,:,:,jp_pcs0_3d + 4)  = zprorca (:,:,:) * zrfact2 * tmask(:,:,:) 
    363362      trc3d(:,:,:,jp_pcs0_3d + 5)  = zprorcad(:,:,:) * zrfact2 * tmask(:,:,:) 
     
    366365      trc3d(:,:,:,jp_pcs0_3d + 8)  = zprorcad(:,:,:) * zrfact2 * tmask(:,:,:) * zysopt(:,:,:) 
    367366      trc3d(:,:,:,jp_pcs0_3d + 9)  = zprofed (:,:,:) * zrfact2 * tmask(:,:,:) 
    368 #if ! defined key_kriest 
     367#  if ! defined key_kriest 
    369368      trc3d(:,:,:,jp_pcs0_3d + 10) = zprofen (:,:,:) * zrfact2 * tmask(:,:,:) 
    370 #endif 
    371  
    372 # else 
    373       zw3d(:,:,:) = zprorca (:,:,:) * zrfact2 * tmask(:,:,:) 
    374       IF( jnt == nrdttrc ) CALL iom_put( "PPPHY" , zw3d ) 
    375       zw3d(:,:,:) = zprorcad(:,:,:) * zrfact2 * tmask(:,:,:) 
    376       IF( jnt == nrdttrc ) CALL iom_put( "PPPHY2", zw3d ) 
    377       zw3d(:,:,:) = zpronew (:,:,:) * zrfact2 * tmask(:,:,:) 
    378       IF( jnt == nrdttrc ) CALL iom_put( "PPNEWN" , zw3d ) 
    379       zw3d(:,:,:) = zpronewd(:,:,:) * zrfact2 * tmask(:,:,:) 
    380       IF( jnt == nrdttrc ) CALL iom_put( "PPNEWD", zw3d ) 
    381       zw3d(:,:,:) = zprorcad(:,:,:) * zrfact2 * tmask(:,:,:) * zysopt(:,:,:) 
    382       IF( jnt == nrdttrc ) CALL iom_put( "PBSi"  , zw3d ) 
    383       zw3d(:,:,:) = zprofed (:,:,:) * zrfact2 * tmask(:,:,:) 
    384       IF( jnt == nrdttrc ) CALL iom_put( "PFeD"  , zw3d ) 
    385       zw3d(:,:,:) = zprofen (:,:,:) * zrfact2 * tmask(:,:,:) 
    386       IF( jnt == nrdttrc ) CALL iom_put( "PFeN"  , zw3d ) 
    387 # endif 
     369#  endif 
     370#endif 
     371 
     372#if defined key_trc_diaadd && defined key_trc_dia3d && defined key_iomput 
     373      zrfact2 = 1.e3 * rfact2r 
     374      IF ( jnt == nrdttrc ) then 
     375         CALL iom_put( "PPPHY" , zprorca (:,:,:) * zrfact2 * tmask(:,:,:) )  ! primary production by nanophyto 
     376         CALL iom_put( "PPPHY2", zprorcad(:,:,:) * zrfact2 * tmask(:,:,:) )  ! primary production by diatom 
     377         CALL iom_put( "PPNEWN", zpronew (:,:,:) * zrfact2 * tmask(:,:,:) )  ! new primary production by nanophyto 
     378         CALL iom_put( "PPNEWD", zpronewd(:,:,:) * zrfact2 * tmask(:,:,:) )  ! new primary production by diatom 
     379         CALL iom_put( "PBSi"  , zprorcad(:,:,:) * zrfact2 * tmask(:,:,:) * zysopt(:,:,:) ) ! biogenic silica production 
     380         CALL iom_put( "PFeD"  , zprofed (:,:,:) * zrfact2 * tmask(:,:,:) )  ! biogenic iron production by diatom 
     381         CALL iom_put( "PFeN"  , zprofen (:,:,:) * zrfact2 * tmask(:,:,:) )  ! biogenic iron production by nanophyto 
     382      ENDIF 
     383#if  defined key_diaar5 
     384      IF ( jnt == nrdttrc ) then 
     385         CALL iom_put( "TPP"  , ( zprorca(:,:,:) + zprorcad(:,:,:) ) * zrfact2 * tmask(:,:,:) )  ! total primary production  
     386         CALL iom_put( "TPNEW", ( zpronew(:,:,:) + zpronewd(:,:,:) ) * zrfact2 * tmask(:,:,:) )  ! total new primary production   
     387         CALL iom_put( "TPBFE", ( zprofen(:,:,:) + zprofed (:,:,:) ) * zrfact2 * tmask(:,:,:) )  ! total biogenic iron production  
     388      ENDIF 
     389      ! primary production by nanophyto ( vertically integrated ) 
     390      zw2d(:,:) = 0. 
     391      DO jk = 1, jpkm1 
     392         zw2d(:,:) = zw2d(:,:) + zprorca (:,:,jk) * fse3t(:,:,jk) * zrfact2 * tmask(:,:,jk) 
     393      ENDDO 
     394      IF ( jnt == nrdttrc ) CALL iom_put( "INTPPPHY" , zw2d )  
     395      ! primary production by diatom ( vertically integrated ) 
     396      zw2d(:,:) = 0. 
     397      DO jk = 1, jpkm1 
     398         zw2d(:,:) = zw2d(:,:) + zprorcad(:,:,jk) * fse3t(:,:,jk) * zrfact2 * tmask(:,:,jk) 
     399      ENDDO 
     400      IF ( jnt == nrdttrc ) CALL iom_put( "INTPPPHY2" , zw2d )  
     401      ! total primary production  ( vertically integrated ) 
     402      zw2d(:,:) = 0. 
     403      DO jk = 1, jpkm1 
     404         zw2d(:,:) = zw2d(:,:) + ( zprorca (:,:,jk) + zprorcad(:,:,jk) ) * fse3t(:,:,jk) * zrfact2 * tmask(:,:,jk) 
     405      ENDDO 
     406      IF ( jnt == nrdttrc ) CALL iom_put( "INTPP" , zw2d )  
     407      ! total new primary production  ( vertically integrated ) 
     408      zw2d(:,:) = 0. 
     409      DO jk = 1, jpkm1 
     410         zw2d(:,:) = zw2d(:,:) + ( zpronew (:,:,jk) + zpronewd(:,:,jk) ) * fse3t(:,:,jk) * zrfact2 * tmask(:,:,jk) 
     411      ENDDO 
     412      IF ( jnt == nrdttrc ) CALL iom_put( "INTPNEW" , zw2d )  
     413      ! total biogenic iron production  ( vertically integrated ) 
     414      zw2d(:,:) = 0. 
     415      DO jk = 1, jpkm1 
     416         zw2d(:,:) = zw2d(:,:) + ( zprofen (:,:,jk) + zprofed(:,:,jk) ) * fse3t(:,:,jk) * zrfact2 * tmask(:,:,jk) 
     417      ENDDO 
     418      IF ( jnt == nrdttrc ) CALL iom_put( "INTPBFE" , zw2d )  
     419      ! biogenic silica production  ( vertically integrated ) 
     420      zw2d(:,:) = 0. 
     421      DO jk = 1, jpkm1 
     422         zw2d(:,:) = zw2d(:,:) + zprorcad(:,:,jk) * zysopt(:,:,jk) * fse3t(:,:,jk) * zrfact2 * tmask(:,:,jk) 
     423      ENDDO 
     424      IF ( jnt == nrdttrc ) CALL iom_put( "INTPBSI" , zw2d )  
     425#endif 
    388426#endif 
    389427 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zsed.F90

    r1735 r1830  
    9696      REAL(wp) :: zrfact2 
    9797# if defined key_iomput 
    98      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d  
    9998     REAL(wp), DIMENSION(jpi,jpj)    ::    zw2d  
    10099# endif 
     
    332331      trc2d(:,:,jp_pcs0_2d + 12) = znitrpot(:,:,1) * 1.e-7 * zrfact2 * fse3t(:,:,1) * tmask(:,:,1) 
    333332# else 
    334       ! write diagnostics 
    335       zw2d(:,:)   =  ( zirondep(:,:,1) + ironsed(:,:,1) * rfact2 ) & 
    336       &            * zrfact2 * fse3t(:,:,1) * tmask(:,:,1)      
     333      ! surface downward net flux of iron 
     334      zw2d(:,:)   =  ( zirondep(:,:,1) + ironsed(:,:,1) * rfact2 ) * zrfact2 * fse3t(:,:,1) * tmask(:,:,1)  
    337335      IF( jnt == nrdttrc ) CALL iom_put( "Irondep", zw2d ) 
    338       zw3d(:,:,:) = znitrpot(:,:,:) * 1.e-7 * zrfact2  * fse3t(:,:,:) * tmask(:,:,:) 
    339       IF( jnt == nrdttrc ) CALL iom_put( "Nfix", zw3d  )  
    340 # endif 
    341  
     336      ! nitrogen fixation at surface 
     337      zw2d(:,:)   =  znitrpot(:,:,1) * 1.e-7 * zrfact2  * fse3t(:,:,1) * tmask(:,:,1) 
     338      IF( jnt == nrdttrc ) CALL iom_put( "Nfix" , zw2d ) 
     339#if defined key_diaar5 
     340      ! nitrogen fixation rate in ocean ( vertically integrated ) 
     341      zw2d(:,:) = 0. 
     342      DO jk = 1, jpkm1 
     343         zw2d(:,:) = zw2d(:,:) + znitrpot(:,:,jk) * 1.e-7 * zrfact2  * fse3t(:,:,jk) * tmask(:,:,jk) 
     344      ENDDO 
     345      IF( jnt == nrdttrc ) CALL iom_put( "INTNFIX" , zw2d ) 
     346# endif 
     347# endif 
    342348# endif 
    343349      ! 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/p4zsink.F90

    r1808 r1830  
    9999#if defined key_trc_diaadd 
    100100      REAL(wp) :: zrfact2 
    101       INTEGER  :: iksed1 
    102 #if defined key_iomput 
    103       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d 
    104 #endif 
     101      INTEGER  :: ik1 
    105102#endif 
    106103      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   znum3d 
     
    286283#if defined key_trc_diaadd 
    287284      zrfact2 = 1.e3 * rfact2r 
    288       iksed1 = iksed + 1 
     285      ik1 = iksed + 1 
    289286#  if ! defined key_iomput 
    290       trc2d(:,:  ,jp_pcs0_2d + 4)  = sinking (:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    291       trc2d(:,:  ,jp_pcs0_2d + 5)  = sinking2(:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    292       trc2d(:,:  ,jp_pcs0_2d + 6)  = sinkfer (:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    293       trc2d(:,:  ,jp_pcs0_2d + 7)  = sinksil (:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    294       trc2d(:,:  ,jp_pcs0_2d + 8)  = sinkcal (:,:,iksed1) * zrfact2 * tmask(:,:,1) 
     287      trc2d(:,:  ,jp_pcs0_2d + 4)  = sinking (:,:,ik1) * zrfact2 * tmask(:,:,1) 
     288      trc2d(:,:  ,jp_pcs0_2d + 5)  = sinking2(:,:,ik1) * zrfact2 * tmask(:,:,1) 
     289      trc2d(:,:  ,jp_pcs0_2d + 6)  = sinkfer (:,:,ik1) * zrfact2 * tmask(:,:,1) 
     290      trc2d(:,:  ,jp_pcs0_2d + 7)  = sinksil (:,:,ik1) * zrfact2 * tmask(:,:,1) 
     291      trc2d(:,:  ,jp_pcs0_2d + 8)  = sinkcal (:,:,ik1) * zrfact2 * tmask(:,:,1) 
    295292      trc3d(:,:,:,jp_pcs0_3d + 11) = sinking (:,:,:)      * zrfact2 * tmask(:,:,:) 
    296293      trc3d(:,:,:,jp_pcs0_3d + 12) = sinking2(:,:,:)      * zrfact2 * tmask(:,:,:) 
     
    301298      trc3d(:,:,:,jp_pcs0_3d + 17) = wsbio4  (:,:,:)                * tmask(:,:,:) 
    302299#else 
    303       zw3d(:,:,:)  = sinking (:,:,:) * zrfact2 * tmask(:,:,:) 
    304       IF( jnt == nrdttrc ) CALL iom_put( "PMO" , zw3d ) 
    305       zw3d(:,:,:)  = sinking2(:,:,:) * zrfact2 * tmask(:,:,:) 
    306       IF( jnt == nrdttrc ) CALL iom_put( "PMO2", zw3d ) 
    307       zw3d(:,:,:)  = sinkfer (:,:,:) * zrfact2 * tmask(:,:,:) 
    308       IF( jnt == nrdttrc ) CALL iom_put( "ExpFe1", zw3d ) 
    309       zw3d(:,:,:)  = sinksil (:,:,:) * zrfact2 * tmask(:,:,:) 
    310       IF( jnt == nrdttrc ) CALL iom_put( "ExpSi", zw3d ) 
    311       zw3d(:,:,:)  = sinkcal (:,:,:) * zrfact2 * tmask(:,:,:) 
    312       IF( jnt == nrdttrc ) CALL iom_put( "ExpCaCO3", zw3d ) 
    313       zw3d(:,:,:)  = sinking (:,:,:) * zrfact2 * tmask(:,:,:) 
    314       IF( jnt == nrdttrc ) CALL iom_put( "POCFlx", zw3d ) 
    315       zw3d(:,:,:)  = sinking2(:,:,:) * zrfact2 * tmask(:,:,:) 
    316       IF( jnt == nrdttrc ) CALL iom_put( "GOCFlx", zw3d ) 
    317       zw3d(:,:,:)  = sinksil (:,:,:) * zrfact2 * tmask(:,:,:) 
    318       IF( jnt == nrdttrc ) CALL iom_put( "SiFlx", zw3d ) 
    319       zw3d(:,:,:)  = sinkcal (:,:,:) * zrfact2 * tmask(:,:,:) 
    320       IF( jnt == nrdttrc ) CALL iom_put( "CaCO3Flx", zw3d ) 
    321       zw3d(:,:,:)  = znum3d  (:,:,:)           * tmask(:,:,:) 
    322       IF( jnt == nrdttrc ) CALL iom_put( "xnum", zw3d ) 
    323       zw3d(:,:,:)  = wsbio3  (:,:,:)           * tmask(:,:,:) 
    324       IF( jnt == nrdttrc ) CALL iom_put( "W1", zw3d ) 
    325       zw3d(:,:,:)  = wsbio4  (:,:,:)           * tmask(:,:,:) 
    326       IF( jnt == nrdttrc ) CALL iom_put( "W2", zw3d ) 
     300      IF( jnt == nrdttrc ) then 
     301        CALL iom_put( "POCFlx"  , sinking (:,:,:)      * zrfact2 * tmask(:,:,:) )  ! POC export 
     302        CALL iom_put( "NumFlx"  , sinking2 (:,:,:)     * zrfact2 * tmask(:,:,:) )  ! Num export 
     303        CALL iom_put( "SiFlx"   , sinksil (:,:,:)      * zrfact2 * tmask(:,:,:) )  ! Silica export 
     304        CALL iom_put( "CaCO3Flx", sinkcal (:,:,:)      * zrfact2 * tmask(:,:,:) )  ! Calcite export 
     305        CALL iom_put( "xnum"    , znum3d  (:,:,:)                * tmask(:,:,:) )  ! Number of particles in aggregats 
     306        CALL iom_put( "W1"      , wsbio3  (:,:,:)                * tmask(:,:,:) )  ! sinking speed of POC 
     307        CALL iom_put( "W2"      , wsbio4  (:,:,:)                * tmask(:,:,:) )  ! sinking speed of aggregats 
     308        CALL iom_put( "PMO"     , sinking (:,:,ik1) * zrfact2 * tmask(:,:,1) )  ! POC export at 100m 
     309        CALL iom_put( "PMO2"    , sinking2(:,:,ik1) * zrfact2 * tmask(:,:,1) )  ! Num export at 100m 
     310        CALL iom_put( "ExpFe1"  , sinkfer (:,:,ik1) * zrfact2 * tmask(:,:,1) )  ! Export of iron at 100m 
     311        CALL iom_put( "ExpSi"   , sinksil (:,:,ik1) * zrfact2 * tmask(:,:,1) )  ! export of silica at 100m 
     312        CALL iom_put( "ExpCaCO3", sinkcal (:,:,ik1) * zrfact2 * tmask(:,:,1) )  ! export of calcite at 100m 
     313     ENDIF 
    327314#  endif 
    328315 
     
    489476#if defined key_trc_dia3d 
    490477      REAL(wp) ::   zrfact2 
    491       INTEGER  ::   iksed1 
    492 #endif 
    493 #if defined key_iomput 
    494       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zw3d 
     478      INTEGER  ::   ik1 
    495479#endif 
    496480      CHARACTER (len=25) :: charout 
     
    613597#if defined key_trc_diaadd 
    614598      zrfact2 = 1.e3 * rfact2r 
    615       iksed1 = iksed + 1 
     599      ik1 = iksed + 1 
    616600#  if ! defined key_iomput 
    617       trc2d(:,:,jp_pcs0_2d + 4) = sinking (:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    618       trc2d(:,:,jp_pcs0_2d + 5) = sinking2(:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    619       trc2d(:,:,jp_pcs0_2d + 6) = sinkfer (:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    620       trc2d(:,:,jp_pcs0_2d + 7) = sinkfer2(:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    621       trc2d(:,:,jp_pcs0_2d + 8) = sinksil (:,:,iksed1) * zrfact2 * tmask(:,:,1) 
    622       trc2d(:,:,jp_pcs0_2d + 9) = sinkcal (:,:,iksed1) * zrfact2 * tmask(:,:,1) 
     601      trc2d(:,:,jp_pcs0_2d + 4) = sinking (:,:,ik1) * zrfact2 * tmask(:,:,1) 
     602      trc2d(:,:,jp_pcs0_2d + 5) = sinking2(:,:,ik1) * zrfact2 * tmask(:,:,1) 
     603      trc2d(:,:,jp_pcs0_2d + 6) = sinkfer (:,:,ik1) * zrfact2 * tmask(:,:,1) 
     604      trc2d(:,:,jp_pcs0_2d + 7) = sinkfer2(:,:,ik1) * zrfact2 * tmask(:,:,1) 
     605      trc2d(:,:,jp_pcs0_2d + 8) = sinksil (:,:,ik1) * zrfact2 * tmask(:,:,1) 
     606      trc2d(:,:,jp_pcs0_2d + 9) = sinkcal (:,:,ik1) * zrfact2 * tmask(:,:,1) 
    623607#  else 
    624       zw3d(:,:,:)  = sinking (:,:,:) * zrfact2 * tmask(:,:,:) 
    625       IF( jnt == nrdttrc ) CALL iom_put( "ExpPOC" , zw3d ) 
    626       zw3d(:,:,:)  = sinking2(:,:,:) * zrfact2 * tmask(:,:,:) 
    627       IF( jnt == nrdttrc ) CALL iom_put( "ExpGOC", zw3d ) 
    628       zw3d(:,:,:)  = sinkfer (:,:,:) * zrfact2 * tmask(:,:,:) 
    629       IF( jnt == nrdttrc ) CALL iom_put( "ExpFe1", zw3d ) 
    630       zw3d(:,:,:)  = sinkfer2(:,:,:) * zrfact2 * tmask(:,:,:) 
    631       IF( jnt == nrdttrc ) CALL iom_put( "ExpFe2", zw3d ) 
    632       zw3d(:,:,:)  = sinksil (:,:,:) * zrfact2 * tmask(:,:,:) 
    633       IF( jnt == nrdttrc ) CALL iom_put( "ExpSi", zw3d ) 
    634       zw3d(:,:,:)  = sinkcal (:,:,:) * zrfact2 * tmask(:,:,:) 
    635       IF( jnt == nrdttrc ) CALL iom_put( "Expcal", zw3d ) 
    636 #  endif 
     608      IF( jnt == nrdttrc )  then 
     609         CALL iom_put( "EPC100"  , ( sinking(:,:,ik1) + sinking2(:,:,ik1) ) * zrfact2 * tmask(:,:,1) ) ! Export of carbon at 100m 
     610         CALL iom_put( "EPFE100" , ( sinkfer(:,:,ik1) + sinkfer2(:,:,ik1) ) * zrfact2 * tmask(:,:,1) ) ! Export of iron at 100m 
     611         CALL iom_put( "EPCAL100",   sinkcal(:,:,ik1)                       * zrfact2 * tmask(:,:,1) ) ! Export of calcite  at 100m 
     612         CALL iom_put( "EPSI100" ,   sinksil(:,:,ik1)                       * zrfact2 * tmask(:,:,1) ) ! Export of biogenic silica at 100m 
     613#if defined key_diaar5 
     614         CALL iom_put( "EXPC"    , ( sinking(:,:,:  ) + sinking2(:,:,:  ) ) * zrfact2 * tmask(:,:,:) ) ! Export of carbon 
     615         CALL iom_put( "EXPFE"   , ( sinkfer(:,:,:  ) + sinkfer2(:,:,:  ) ) * zrfact2 * tmask(:,:,:) ) ! Export of iron  
     616         CALL iom_put( "EXPCAL"  ,   sinkcal(:,:,:  )                       * zrfact2 * tmask(:,:,:) ) ! Export of calcite  
     617         CALL iom_put( "EXPSI"   ,   sinksil(:,:,:  )                       * zrfact2 * tmask(:,:,:) ) ! Export of biogenic 
     618#endif 
     619      ENDIF 
     620#endif 
    637621#endif 
    638622      ! 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/PISCES/sms_pisces.F90

    r1808 r1830  
    6464#if defined key_trc_dia3d 
    6565   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   prodcal    !: Calcite production 
     66   REAL(wp), DIMENSION(jpi,jpj,jpk) ::   grazing    !: Total zooplankton grazing 
    6667#endif 
    6768 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/par_trc.F90

    r1254 r1830  
    1818   USE par_lobster   ! LOBSTER model 
    1919   USE par_pisces    ! PISCES  model 
     20   USE par_c14b      ! C14 bomb tracer 
    2021   USE par_cfc       ! CFC 11 and 12 tracers 
    21    USE par_c14b      ! C14 bomb tracer  
    2222   USE par_my_trc    ! user defined passive tracers 
    2323 
     
    2727   ! Passive tracers : Total size 
    2828   ! ---------------               ! total number of passive tracers, of 2d and 3d output and trend arrays 
    29    INTEGER, PUBLIC, PARAMETER ::   jptra    =  jp_lobster    + jp_pisces     + jp_cfc     + jp_c14b     + jp_my_trc 
    30    INTEGER, PUBLIC, PARAMETER ::   jpdia2d  =  jp_lobster_2d + jp_pisces_2d  + jp_cfc_2d  + jp_c14b_2d  + jp_my_trc_2d 
    31    INTEGER, PUBLIC, PARAMETER ::   jpdia3d  =  jp_lobster_3d + jp_pisces_3d  + jp_cfc_3d  + jp_c14b_3d  + jp_my_trc_3d 
     29   INTEGER, PUBLIC, PARAMETER ::   jptra    =  jp_lobster    + jp_pisces     + jp_cfc     + jp_my_trc 
     30   INTEGER, PUBLIC, PARAMETER ::   jpdia2d  =  jp_lobster_2d + jp_pisces_2d  + jp_cfc_2d  + jp_my_trc_2d 
     31   INTEGER, PUBLIC, PARAMETER ::   jpdia3d  =  jp_lobster_3d + jp_pisces_3d  + jp_cfc_3d  + jp_my_trc_3d 
    3232   !                     ! total number of sms diagnostic arrays 
    33    INTEGER, PUBLIC, PARAMETER ::   jpdiabio = jp_lobster_trd + jp_pisces_trd + jp_cfc_trd + jp_c14b_trd + jp_my_trc_trd 
     33   INTEGER, PUBLIC, PARAMETER ::   jpdiabio = jp_lobster_trd + jp_pisces_trd + jp_cfc_trd + jp_my_trc_trd 
    3434    
    3535   !  1D configuration ("key_c1d") 
     
    4040   LOGICAL, PUBLIC, PARAMETER ::   lk_trc_c1d   = .FALSE.  !: 1D pass. tracer configuration flag 
    4141# endif 
    42  
    4342   ! Passive tracers : size for TRP trends diagnotics (used if 'key_trc_diatrd' defined) 
    44 #if defined key_trcldf_eiv 
    45 # if defined key_trcdmp 
    46    INTEGER, PARAMETER :: jpdiatrc = 11      !: trends: 3*(advection + diffusion + eiv ) + damping + sms 
    47 # else 
    48    INTEGER, PARAMETER :: jpdiatrc = 10      !: trends: 3*(advection + diffusion + eiv )           + sms 
    49 # endif 
    50 #else 
    51 # if defined key_trcdmp 
    52    INTEGER, PARAMETER :: jpdiatrc =  8      !: trends: 3*(advection + diffusion       ) + damping + sms 
    53 # else 
    54    INTEGER, PARAMETER :: jpdiatrc =  7      !: trends: 3*(advection + diffusion       ) + damping + sms 
    55 # endif 
     43# if defined key_trc_diatrd 
     44   ! Passive tracers : size for TRP trends diagnotics (used if 'key_trc_diatrd' defined) 
     45   INTEGER, PARAMETER ::   jptrc_xad     =  1   !: x- horizontal advection 
     46   INTEGER, PARAMETER ::   jptrc_yad     =  2   !: y- horizontal advection 
     47   INTEGER, PARAMETER ::   jptrc_zad     =  3   !: z- vertical   advection 
     48   INTEGER, PARAMETER ::   jptrc_xdf     =  4   !: lateral       diffusion 
     49   INTEGER, PARAMETER ::   jptrc_ydf     =  5   !: lateral       diffusion 
     50   INTEGER, PARAMETER ::   jptrc_zdf     =  6   !: vertical diffusion (Kz) 
     51   INTEGER, PARAMETER ::   jptrc_sbc     =  7   !: surface boundary condition 
     52#if ! defined key_trcldf_eiv && ! defined key_trcdmp 
     53   INTEGER, PARAMETER ::   jpdiatrc      =  7  !: trends: 3*(advection + diffusion       ) + sbc 
     54#endif 
     55#if defined key_trcldf_eiv && defined key_trcdmp 
     56   INTEGER, PARAMETER ::   jptrc_xei     =  8   !: x- horiz. EIV advection 
     57   INTEGER, PARAMETER ::   jptrc_yei     =  9   !: y- horiz. EIV advection 
     58   INTEGER, PARAMETER ::   jptrc_zei     = 10   !: z- vert.  EIV advection 
     59   INTEGER, PARAMETER ::   jptrc_dmp     = 11   !: damping 
     60   INTEGER, PARAMETER ::   jpdiatrc      = 11   !: trends: 3*(advection + diffusion + eiv ) + sbc + damping 
     61#endif 
     62#if defined key_trcldf_eiv && ! defined key_trcdmp 
     63   INTEGER, PARAMETER ::   jptrc_xei     =  8   !: x- horiz. EIV advection 
     64   INTEGER, PARAMETER ::   jptrc_yei     =  9   !: y- horiz. EIV advection 
     65   INTEGER, PARAMETER ::   jptrc_zei     = 10   !: z- vert.  EIV advection 
     66   INTEGER, PARAMETER ::   jpdiatrc      = 10   !: trends: 3*(advection + diffusion + eiv ) + sbc  
     67#endif 
     68#if ! defined key_trcldf_eiv && defined key_trcdmp 
     69   INTEGER, PARAMETER ::   jptrc_dmp     =  8   !: damping 
     70   INTEGER, PARAMETER ::   jpdiatrc      =  8   !: trends: 3*(advection + diffusion       ) + sbc + damping 
     71#endif 
    5672#endif 
    5773 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/trcdia.F90

    r1715 r1830  
    2121   !! trcdib_wr   : outputs of biological fields 
    2222   !!---------------------------------------------------------------------- 
    23    USE dom_oce         ! ocean space and time domain variables  
     23   USE dom_oce         ! ocean space and time domain variables 
    2424   USE oce_trc 
     25   USE trp_trc 
    2526   USE trc 
    26    USE trp_trc 
     27   USE par_trc 
     28   USE trctrp 
    2729   USE trdmld_trc_oce, ONLY : luttrd 
     30   USE iom 
    2831   USE dianam    ! build name of file (routine) 
    2932   USE in_out_manager  ! I/O manager 
     
    4144   INTEGER  ::   ndimt50   !: number of ocean points in index array 
    4245   INTEGER  ::   ndimt51   !: number of ocean points in index array 
    43    REAL(wp) ::   xjulian   !: ????   not DOCTOR ! 
     46   REAL(wp) ::   zjulian   !: ????   not DOCTOR ! 
    4447   INTEGER , DIMENSION (jpij*jpk) ::   ndext50   !: integer arrays for ocean 3D index 
    4548   INTEGER , DIMENSION (jpij)     ::   ndext51   !: integer arrays for ocean surface index 
     
    6467   !!---------------------------------------------------------------------- 
    6568   !! NEMO/TOP 1.0 , LOCEAN-IPSL (2005)  
    66    !! $Id$  
     69   !! $Header:$  
    6770   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
    6871   !!---------------------------------------------------------------------- 
     
    7073CONTAINS 
    7174 
    72    SUBROUTINE trc_dia( kt 
     75   SUBROUTINE trc_dia( kt, kindic 
    7376      !!--------------------------------------------------------------------- 
    7477      !!                     ***  ROUTINE trc_dia  *** 
     
    7780      !!--------------------------------------------------------------------- 
    7881      INTEGER, INTENT( in ) :: kt 
    79       INTEGER               :: kindic 
     82      INTEGER         :: kindic 
    8083      !!--------------------------------------------------------------------- 
    8184       
     
    110113      LOGICAL ::   ll_print = .FALSE. 
    111114      CHARACTER (len=40) :: clhstnam, clop 
    112 #if defined key_off_tra 
    113       INTEGER ::   inum = 11             ! temporary logical unit 
    114 #endif 
    115115      CHARACTER (len=20) :: cltra, cltrau 
    116116      CHARACTER (len=80) :: cltral 
    117117      REAL(wp) :: zsto, zout, zdt 
    118       INTEGER  :: iimi, iima, ijmi, ijma, ipk, it, itmod 
     118      INTEGER  :: iimi, iima, ijmi, ijma, ipk, it 
    119119      !!---------------------------------------------------------------------- 
    120120 
     
    128128      ! Define frequency of output and means 
    129129      zdt = rdt 
    130       IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!) 
    131       ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time) 
    132       ENDIF 
    133130# if defined key_diainstant 
    134131      zsto = nwritetrc * rdt 
    135       clop = "inst("//TRIM(clop)//")" 
     132      clop = 'inst(only(x))' 
    136133# else 
    137134      zsto = zdt 
    138       clop = "ave("//TRIM(clop)//")" 
     135      clop = 'ave(only(x))' 
    139136# endif 
    140137      zout = nwritetrc * zdt 
     
    146143 
    147144      ! define time axis 
    148       itmod = kt - nittrc000 + 1 
    149       it    = kt 
     145      it = kt - nittrc000 + 1 
    150146 
    151147      ! Define NETCDF files and fields at beginning of first time step 
     
    157153 
    158154         ! Compute julian date from starting date of the run 
    159          CALL ymds2ju( nyear, nmonth, nday, rdt, xjulian ) 
    160          xjulian = xjulian - adatrj   !   set calendar origin to the beginning of the experiment 
     155         CALL ymds2ju( nyear, nmonth, nday, 0.0, zjulian ) 
    161156         IF(lwp)WRITE(numout,*)' '   
    162157         IF(lwp)WRITE(numout,*)' Date 0 used :', nittrc000                         & 
    163158            &                 ,' YEAR ', nyear, ' MONTH ', nmonth, ' DAY ', nday   & 
    164             &                 ,'Julian day : ', xjulian   
    165    
     159            &                 ,'Julian day : ', zjulian     
    166160         IF(lwp) WRITE(numout,*) ' indexes of zoom = ', iimi, iima, ijmi, ijma,  & 
    167161            &                    ' limit storage in depth = ', ipk 
    168162 
    169 #if defined key_off_tra 
    170         ! WRITE root name in date.file for use by postpro 
    171          IF(lwp) THEN 
    172             CALL dia_nam( clhstnam, nwritetrc,' ' ) 
    173             CALL ctl_opn( inum, 'date.file', 'REPLACE', 'FORMATTED', 'SEQUENTIAL', -1, numout, lwp, narea ) 
    174             WRITE(inum,*) clhstnam 
    175             CLOSE(inum) 
    176          ENDIF 
    177 #endif 
    178  
    179          ! Define the NETCDF files for passive tracer concentration 
     163 
     164! Define the NETCDF files for passive tracer concentration 
     165 
    180166         CALL dia_nam( clhstnam, nwritetrc, 'ptrc_T' ) 
    181167         IF(lwp)WRITE(numout,*)" Name of NETCDF file ", clhstnam 
    182  
    183          ! Horizontal grid : glamt and gphit 
     168! Horizontal grid : glamt and gphit 
    184169         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,     & 
    185170            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         &  
    186             &          nittrc000-ndttrc, xjulian, zdt, nhorit5, nit5 , domain_id=nidom) 
    187  
    188          ! Vertical grid for tracer : gdept 
    189          CALL histvert( nit5, 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepit5) 
    190  
    191          ! Index of ocean points in 3D and 2D (surface) 
    192          CALL wheneq( jpi*jpj*ipk, tmask, 1, 1., ndext50, ndimt50 ) 
    193          CALL wheneq( jpi*jpj    , tmask, 1, 1., ndext51, ndimt51 ) 
    194  
    195          ! Declare all the output fields as NETCDF variables 
     171            &          0, zjulian, zdt, nhorit5, nit5 , domain_id=nidom) 
     172! Vertical grid for tracer : gdept 
     173         CALL histvert( nit5, 'deptht', 'Vertical T levels', & 
     174            &            'm', ipk, gdept_0, ndepit5) 
     175 
     176! Index of ocean points in 3D and 2D (surface) 
     177         CALL wheneq( jpi*jpj*ipk,tmask,1,1.,ndext50,ndimt50 ) 
     178         CALL wheneq( jpi*jpj,tmask,1,1.,ndext51,ndimt51 ) 
     179 
     180! Declare all the output fields as NETCDF variables 
     181 
     182! tracer concentrations 
    196183         DO jn = 1, jptra 
    197184            IF( lutsav(jn) ) THEN 
     
    200187               cltrau = ctrcun(jn)   ! UNIT for tracer 
    201188               CALL histdef( nit5, cltra, cltral, cltrau, jpi, jpj, nhorit5,  & 
    202                   &          ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout )  
     189                  &               ipk, 1, ipk,  ndepit5, 32, clop, zsto, zout)  
    203190            ENDIF 
    204191         END DO 
     
    215202      ! --------------------------------------- 
    216203 
    217       IF( lwp .AND. MOD( itmod, nwritetrc ) == 0 ) THEN 
     204      IF( lwp .AND. MOD( kt, nwritetrc ) == 0 ) THEN 
    218205         WRITE(numout,*) 'trcdit_wr : write NetCDF passive tracer concentrations at ', kt, 'time-step' 
    219206         WRITE(numout,*) '~~~~~~~~~ ' 
     
    221208 
    222209      DO jn = 1, jptra 
    223          cltra = ctrcnm(jn)      ! short title for tracer 
    224          IF( lutsav(jn) ) CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 ) 
     210         IF( lutsav(jn) ) THEN 
     211            cltra = ctrcnm(jn)      ! short title for tracer 
     212            CALL histwrite( nit5, cltra, it, trn(:,:,:,jn), ndimt50, ndext50 ) 
     213         ENDIF 
    225214      END DO 
     215 
     216      ! synchronise file 
     217      IF( MOD( kt, nwritetrc ) == 0 .OR. kindic < 0 )   CALL histsync( nit5 ) 
     218 
    226219 
    227220      ! close the file  
     
    229222      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nit5 ) 
    230223      ! 
    231  
    232224   END SUBROUTINE trcdit_wr 
    233225 
     
    244236      !! 
    245237      !!        At each time step call histdef to compute the mean if necessary 
    246       !!        Each nwritetrd time step, output the instantaneous or mean fields 
     238      !!        Each nwritetrc time step, output the instantaneous or mean fields 
    247239      !! 
    248240      !!        IF kindic <0, output of fields before the model interruption. 
     
    258250      CHARACTER (len=80) ::   cltral 
    259251      CHARACTER (len=10) ::   csuff 
    260       INTEGER  ::   jn, jl 
    261       INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod 
     252      INTEGER  ::   jn, jl, ikn 
     253      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it 
    262254      REAL(wp) ::   zsto, zout, zdt 
    263255      !!---------------------------------------------------------------------- 
     
    265257      ! 0. Initialisation 
    266258      ! ----------------- 
    267        
    268259 
    269260      ! local variable for debugging 
     
    273264      ! Define frequency of output and means 
    274265      zdt = rdt 
    275       IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!) 
    276       ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time) 
    277       ENDIF 
    278266#  if defined key_diainstant 
    279267      zsto = nwritetrd * rdt 
    280       clop = "inst("//TRIM(clop)//")" 
     268      clop = 'inst(only(x))' 
    281269#  else 
    282270      zsto = zdt 
    283       clop = "ave("//TRIM(clop)//")" 
     271      clop = 'ave(only(x))' 
    284272#  endif 
    285273      zout = nwritetrd * zdt 
     
    291279 
    292280      ! define time axis 
    293       itmod = kt - nittrc000 + 1 
    294       it    = kt 
     281      it = kt - nittrc000 + 1 
    295282 
    296283      ! Define the NETCDF files (one per tracer) 
     
    313300               CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,       & 
    314301                  &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,   & 
    315                   &          nittrc000-ndttrc, xjulian, zdt, nhorit6(jn),  & 
     302                  &          0, zjulian, rdt, nhorit6(jn),           & 
    316303                  &          nit6(jn) , domain_id=nidom ) 
    317304 
    318305               ! Vertical grid for tracer trend - one per each tracer IF needed 
    319                CALL histvert( nit6(jn), 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepit6(jn) )  
     306               CALL histvert( nit6(jn), 'deptht', 'Vertical T levels',   & 
     307                  &           'm', ipk, gdept_0, ndepit6(jn) )  
    320308             END IF 
    321309          END DO 
    322310 
    323311          ! Declare all the output fields as NETCDF variables 
    324  
    325           ! trends for tracer concentrations 
    326312          DO jn = 1, jptra 
    327313            IF( luttrd(jn) ) THEN 
    328314                DO jl = 1, jpdiatrc 
    329                   IF( jl == 1 ) THEN 
     315                  IF( jl == jptrc_xad ) THEN 
    330316                      ! short and long title for x advection for tracer 
    331317                      WRITE (cltra,'("XAD_",16a)') ctrcnm(jn) 
    332                       WRITE (cltral,'("X advective trend for ",58a)')  & 
    333                          &      ctrcnl(jn)(1:58) 
    334                   END IF 
    335                   IF( jl == 2 ) THEN 
     318                      WRITE (cltral,'("X advective trend for ",58a)') ctrcnl(jn)(1:58) 
     319                  END IF 
     320                  IF( jl == jptrc_yad ) THEN 
    336321                      ! short and long title for y advection for tracer 
    337322                      WRITE (cltra,'("YAD_",16a)') ctrcnm(jn) 
    338                       WRITE (cltral,'("Y advective trend for ",58a)')  & 
    339                          &      ctrcnl(jn)(1:58) 
    340                   END IF 
    341                   IF( jl == 3 ) THEN 
     323                      WRITE (cltral,'("Y advective trend for ",58a)') ctrcnl(jn)(1:58) 
     324                  END IF 
     325                  IF( jl == jptrc_zad ) THEN 
    342326                      ! short and long title for Z advection for tracer 
    343327                      WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn) 
    344                       WRITE (cltral,'("Z advective trend for ",58a)')  & 
    345                          &      ctrcnl(jn)(1:58) 
    346                   END IF 
    347                   IF( jl == 4 ) THEN 
     328                      WRITE (cltral,'("Z advective trend for ",58a)') ctrcnl(jn)(1:58) 
     329                  END IF 
     330                  IF( jl == jptrc_xdf ) THEN 
    348331                      ! short and long title for X diffusion for tracer 
    349332                      WRITE (cltra,'("XDF_",16a)') ctrcnm(jn) 
    350                       WRITE (cltral,'("X diffusion trend for ",58a)')  & 
    351                          &      ctrcnl(jn)(1:58) 
    352                   END IF 
    353                   IF( jl == 5 ) THEN 
     333                      WRITE (cltral,'("X diffusion trend for ",58a)') ctrcnl(jn)(1:58) 
     334                  END IF 
     335                  IF( jl == jptrc_ydf ) THEN 
    354336                      ! short and long title for Y diffusion for tracer 
    355337                      WRITE (cltra,'("YDF_",16a)') ctrcnm(jn) 
    356                       WRITE (cltral,'("Y diffusion trend for ",58a)')  & 
    357                          &      ctrcnl(jn)(1:58) 
    358                   END IF 
    359                   IF( jl == 6 ) THEN 
     338                      WRITE (cltral,'("Y diffusion trend for ",58a)') ctrcnl(jn)(1:58) 
     339                  END IF 
     340                  IF( jl == jptrc_zdf ) THEN 
    360341                      ! short and long title for Z diffusion for tracer 
    361342                      WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn) 
    362                       WRITE (cltral,'("Z diffusion trend for ",58a)')  & 
    363                          &      ctrcnl(jn)(1:58) 
     343                      WRITE (cltral,'("Z diffusion trend for ",58a)') ctrcnl(jn)(1:58) 
    364344                  END IF 
    365345# if defined key_trcldf_eiv 
    366                   IF( jl == 7 ) THEN 
     346                  IF( jl == jptrc_xei ) THEN 
    367347                      ! short and long title for x gent velocity for tracer 
    368348                      WRITE (cltra,'("XGV_",16a)') ctrcnm(jn) 
    369                       WRITE (cltral,'("X gent velocity trend for ",53a)')  & 
    370                          &      ctrcnl(jn)(1:53) 
    371                   END IF 
    372                   IF( jl == 8 ) THEN 
     349                      WRITE (cltral,'("X gent velocity trend for ",53a)') ctrcnl(jn)(1:53) 
     350                  END IF 
     351                  IF( jl == jptrc_yei ) THEN 
    373352                      ! short and long title for y gent velocity for tracer 
    374353                      WRITE (cltra,'("YGV_",16a)') ctrcnm(jn) 
    375                       WRITE (cltral,'("Y gent velocity trend for ",53a)')  & 
    376                          &      ctrcnl(jn)(1:53) 
    377                   END IF 
    378                   IF( jl == 9 ) THEN 
     354                      WRITE (cltral,'("Y gent velocity trend for ",53a)') ctrcnl(jn)(1:53) 
     355                  END IF 
     356                  IF( jl == jptrc_zei ) THEN 
    379357                      ! short and long title for Z gent velocity for tracer 
    380358                      WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn) 
    381                       WRITE (cltral,'("Z gent velocity trend for ",53a)')  & 
    382                          &      ctrcnl(jn)(1:53) 
     359                      WRITE (cltral,'("Z gent velocity trend for ",53a)') ctrcnl(jn)(1:53) 
    383360                  END IF 
    384361# endif 
    385362# if defined key_trcdmp 
    386                   IF( jl == jpdiatrc - 1 ) THEN 
     363                  IF( jl == jptrc_dmp ) THEN 
    387364                      ! last trends for tracer damping : short and long title 
    388365                      WRITE (cltra,'("TDM_",16a)') ctrcnm(jn) 
    389                       WRITE (cltral,'("Tracer damping trend for ",55a)')  & 
    390                          &      ctrcnl(jn)(1:55) 
    391                   END IF 
    392 # endif 
    393                   IF( jl == jpdiatrc ) THEN 
     366                      WRITE (cltral,'("Tracer damping trend for ",55a)') ctrcnl(jn)(1:55) 
     367                  END IF 
     368# endif 
     369                  IF( jl == jptrc_sbc ) THEN 
    394370                      ! last trends for tracer damping : short and long title 
    395371                      WRITE (cltra,'("SBC_",16a)') ctrcnm(jn) 
    396                       WRITE (cltral,'("Surface boundary flux ",58a)')  & 
    397                       &      ctrcnl(jn)(1:58) 
    398                   END IF 
    399  
     372                      WRITE (cltral,'("Surface boundary flux ",58a)') ctrcnl(jn)(1:55) 
     373                  END IF 
     374                      WRITE (cltral,'("Surface boundary flux ",58a)') ctrcnl(jn)(1:55) 
     375                  END IF 
    400376                  CALL FLUSH( numout ) 
    401377                  cltrau = ctrcun(jn)      ! UNIT for tracer /trends 
     
    425401      ! trends for tracer concentrations 
    426402 
    427       IF( lwp .AND. MOD( itmod, nwritetrd ) == 0 ) THEN 
     403      IF( lwp .AND. MOD( kt, nwritetrd ) == 0 ) THEN 
    428404         WRITE(numout,*) 'trcdid_wr : write NetCDF dynamical trends at ', kt, 'time-step' 
    429405         WRITE(numout,*) '~~~~~~ ' 
     
    432408      DO jn = 1, jptra 
    433409         IF( luttrd(jn) ) THEN 
     410            ikn = ikeep(jn) 
    434411            DO jl = 1, jpdiatrc 
    435                ! short titles  
    436                IF( jl == 1)   WRITE (cltra,'("XAD_",16a)') ctrcnm(jn)      ! x advection for tracer 
    437                IF( jl == 2)   WRITE (cltra,'("YAD_",16a)') ctrcnm(jn)      ! z advection for tracer 
    438                IF( jl == 3)   WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn)      ! z advection for tracer 
    439                IF( jl == 4)   WRITE (cltra,'("XDF_",16a)') ctrcnm(jn)      ! x diffusion for tracer 
    440                IF( jl == 5)   WRITE (cltra,'("YDF_",16a)') ctrcnm(jn)      ! y diffusion for tracer 
    441                IF( jl == 6)   WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn)      ! z diffusion for tracer 
     412               ! short titles 
     413               IF( jl == jptrc_xad)   WRITE (cltra,'("XAD_",16a)') ctrcnm(jn) 
     414               IF( jl == jptrc_yad)   WRITE (cltra,'("YAD_",16a)') ctrcnm(jn) 
     415               IF( jl == jptrc_zad)   WRITE (cltra,'("ZAD_",16a)') ctrcnm(jn) 
     416               IF( jl == jptrc_xdf)   WRITE (cltra,'("XDF_",16a)') ctrcnm(jn) 
     417               IF( jl == jptrc_ydf)   WRITE (cltra,'("YDF_",16a)') ctrcnm(jn) 
     418               IF( jl == jptrc_zdf)   WRITE (cltra,'("ZDF_",16a)') ctrcnm(jn) 
    442419# if defined key_trcldf_eiv 
    443                IF( jl == 7)   WRITE (cltra,'("XGV_",16a)') ctrcnm(jn)      ! x gent velocity for tracer 
    444                IF( jl == 8)   WRITE (cltra,'("YGV_",16a)') ctrcnm(jn)      ! y gent velocity for tracer 
    445                IF( jl == 9)   WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn)      ! z gent velocity for tracer 
     420               IF( jl == jptrc_xei)   WRITE (cltra,'("XGV_",16a)') ctrcnm(jn) 
     421               IF( jl == jptrc_yei)   WRITE (cltra,'("YGV_",16a)') ctrcnm(jn) 
     422               IF( jl == jptrc_zei)   WRITE (cltra,'("ZGV_",16a)') ctrcnm(jn) 
    446423# endif 
    447424# if defined key_trcdmp 
    448                IF( jl == jpdiatrc - 1 )   WRITE (cltra,'("TDM_",16a)') ctrcnm(jn)      ! damping 
    449 # endif 
    450                IF( jl == jpdiatrc )   WRITE (cltra,'("SBC_",a)') ctrcnm(jn)      ! surface boundary conditions 
     425               IF( jl == jptrc_dmp )  WRITE (cltra,'("TDM_",16a)') ctrcnm(jn) 
     426# endif 
     427               IF( jl == jptrc_sbc )  WRITE (cltra,'("SBC_",16a)') ctrcnm(jn) 
    451428               ! 
    452                CALL histwrite(nit6(jn), cltra, it, trtrd(:,:,:,ikeep(jn),jl),ndimt50, ndext50) 
     429               CALL histwrite(nit6(jn), cltra, it, trtrd(:,:,:,ikn,jl),ndimt50, ndext50) 
    453430            END DO 
    454431         END IF 
    455432      END DO 
     433 
     434      ! synchronise FILE 
     435      IF( MOD( kt, nwritetrd ) == 0 .OR. kindic < 0 ) THEN 
     436         DO jn = 1, jptra 
     437            IF (luttrd(jn))   CALL histsync( nit6(jn) ) 
     438         END DO 
     439      ENDIF 
    456440 
    457441      ! Closing all files 
     
    463447      ENDIF 
    464448      ! 
    465  
    466449   END SUBROUTINE trcdid_wr 
    467450 
     
    486469      !! 
    487470      !!        At each time step call histdef to compute the mean if necessary 
    488       !!        Each nwritedia time step, output the instantaneous or mean fields 
     471      !!        Each nwritetrc time step, output the instantaneous or mean fields 
    489472      !! 
    490473      !!        IF kindic <0, output of fields before the model interruption. 
     
    499482      CHARACTER (len=20) ::   cltra, cltrau 
    500483      CHARACTER (len=80) ::   cltral 
    501       INTEGER  ::   jl 
    502       INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod 
     484      INTEGER  ::   jn 
     485      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it 
    503486      REAL(wp) ::   zsto, zout, zdt 
    504487      !!---------------------------------------------------------------------- 
     
    506489      ! Initialisation 
    507490      ! -------------- 
    508        
     491 
    509492      ! local variable for debugging 
    510493      ll_print = .FALSE. 
     
    513496      ! Define frequency of output and means 
    514497      zdt = rdt 
    515       IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!) 
    516       ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time) 
    517       ENDIF 
    518498#  if defined key_diainstant 
    519       zsto = nwritedia * zdt 
    520       clop = "inst("//TRIM(clop)//")" 
     499      zsto=nwritedia*zdt 
     500      clop='inst(only(x))' 
    521501#  else 
    522       zsto = zdt 
    523       clop = "ave("//TRIM(clop)//")" 
     502      zsto=zdt 
     503      clop='ave(only(x))' 
    524504#  endif 
    525       zout = nwritedia * zdt 
     505      zout=nwritedia*zdt 
    526506 
    527507      ! Define indices of the horizontal output zoom and vertical limit storage 
     
    531511 
    532512      ! define time axis 
    533       itmod = kt - nittrc000 + 1 
    534       it    = kt 
     513      it = kt - nittrc000 + 1 
    535514 
    536515      ! 1. Define NETCDF files and fields at beginning of first time step 
     
    545524         ! Define the T grid file for tracer auxiliary files 
    546525 
    547          CALL dia_nam( clhstnam, nwritedia, 'diad_T' ) 
     526         CALL dia_nam( clhstnam, nwrite, 'diad_T' ) 
    548527         IF(lwp) WRITE(numout,*) " Name of NETCDF file ", clhstnam 
    549528 
     
    552531         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,             & 
    553532            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,         & 
    554             &          nittrc000-ndttrc, xjulian, zdt, nhoritd, nitd , domain_id=nidom ) 
     533            &          0, zjulian, zdt, nhoritd, nitd , domain_id=nidom ) 
    555534 
    556535         ! Vertical grid for 2d and 3d arrays 
    557536 
    558          CALL histvert( nitd, 'deptht', 'Vertical T levels','m', ipk, gdept_0, ndepitd) 
     537         CALL histvert( nitd, 'deptht', 'Vertical T levels',   & 
     538            &           'm', ipk, gdept_0, ndepitd) 
    559539 
    560540         ! Declare all the output fields as NETCDF variables 
    561541 
    562542         ! more 3D horizontal arrays 
    563          DO jl = 1, jpdia3d 
    564             cltra  = ctrc3d(jl)   ! short title for 3D diagnostic 
    565             cltral = ctrc3l(jl)   ! long title for 3D diagnostic 
    566             cltrau = ctrc3u(jl)   ! UNIT for 3D diagnostic 
     543         DO jn = 1, jpdia3d 
     544            cltra  = ctrc3d(jn)   ! short title for 3D diagnostic 
     545            cltral = ctrc3l(jn)   ! long title for 3D diagnostic 
     546            cltrau = ctrc3u(jn)   ! UNIT for 3D diagnostic 
    567547            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,   & 
    568548               &          ipk, 1, ipk,  ndepitd, 32, clop, zsto, zout ) 
     
    570550 
    571551         ! more 2D horizontal arrays 
    572          DO jl = 1, jpdia2d 
    573             cltra  = ctrc2d(jl)    ! short title for 2D diagnostic 
    574             cltral = ctrc2l(jl)   ! long title for 2D diagnostic 
    575             cltrau = ctrc2u(jl)   ! UNIT for 2D diagnostic 
     552         DO jn = 1, jpdia2d 
     553            cltra  = ctrc2d(jn)    ! short title for 2D diagnostic 
     554            cltral = ctrc2l(jn)   ! long title for 2D diagnostic 
     555            cltrau = ctrc2u(jn)   ! UNIT for 2D diagnostic 
    576556            CALL histdef( nitd, cltra, cltral, cltrau, jpi, jpj, nhoritd,  & 
    577557               &          1, 1, 1,  -99, 32, clop, zsto, zout ) 
     
    592572      ! --------------------- 
    593573 
    594       IF( lwp .AND. MOD( itmod, nwritedia ) == 0 ) THEN 
     574      IF( lwp .AND. MOD( kt, nwritedia ) == 0 ) THEN 
    595575         WRITE(numout,*) 'trcdii_wr : write NetCDF additional arrays at ', kt, 'time-step' 
    596576         WRITE(numout,*) '~~~~~~ ' 
     
    598578 
    599579      ! more 3D horizontal arrays 
    600       DO jl = 1, jpdia3d 
    601          cltra = ctrc3d(jl)   ! short title for 3D diagnostic 
    602          CALL histwrite( nitd, cltra, it, trc3d(:,:,:,jl), ndimt50 ,ndext50) 
     580      DO jn = 1, jpdia3d 
     581         cltra = ctrc3d(jn)   ! short title for 3D diagnostic 
     582         CALL histwrite( nitd, cltra, it, trc3d(:,:,:,jn), ndimt50 ,ndext50) 
    603583      END DO 
    604584 
    605585      ! more 2D horizontal arrays 
    606       DO jl = 1, jpdia2d 
    607          cltra = ctrc2d(jl)   ! short title for 2D diagnostic 
    608          CALL histwrite(nitd, cltra, it, trc2d(:,:,jl), ndimt51  ,ndext51) 
     586      DO jn = 1, jpdia2d 
     587         cltra = ctrc2d(jn)   ! short title for 2D diagnostic 
     588         CALL histwrite(nitd, cltra, it, trc2d(:,:,jn), ndimt51  ,ndext51) 
    609589      END DO 
     590 
     591      ! synchronise FILE 
     592      IF( MOD( kt, nwritedia ) == 0 .OR. kindic < 0 )   CALL histsync( nitd ) 
    610593 
    611594      ! Closing all files 
     
    613596      IF( kt == nitend .OR. kindic < 0 )   CALL histclo(nitd) 
    614597      ! 
    615  
    616598   END SUBROUTINE trcdii_wr 
    617599 
     
    636618      !! 
    637619      !!        At each time step call histdef to compute the mean if necessary 
    638       !!        Each nwritebio time step, output the instantaneous or mean fields 
     620      !!        Each nwritetrc time step, output the instantaneous or mean fields 
    639621      !! 
    640622      !!        IF kindic <0, output of fields before the model interruption. 
     
    650632      CHARACTER (len=20) ::   cltra, cltrau 
    651633      CHARACTER (len=80) ::   cltral 
    652       INTEGER  ::   ji, jj, jk, jl 
    653       INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it, itmod 
     634      INTEGER  ::   ji, jj, jk, jn 
     635      INTEGER  ::   iimi, iima, ijmi, ijma, ipk, it 
    654636      REAL(wp) ::   zsto, zout, zdt 
    655637      !!---------------------------------------------------------------------- 
     
    658640      ! -------------- 
    659641 
    660        
    661642      ! local variable for debugging 
    662643      ll_print = .FALSE. 
     
    665646      ! Define frequency of output and means 
    666647      zdt = rdt 
    667       IF( ln_mskland )   THEN   ;   clop = "only(x)"   ! put 1.e+20 on land (very expensive!!) 
    668       ELSE                      ;   clop = "x"         ! no use of the mask value (require less cpu time) 
    669       ENDIF 
    670648#        if defined key_diainstant 
    671       zsto = nwritebio * zdt 
    672       clop = "inst("//TRIM(clop)//")" 
     649      zsto=nwritebio*zdt 
     650      clop='inst(only(x))' 
    673651#        else 
    674       zsto = zdt 
    675       clop = "ave("//TRIM(clop)//")" 
     652      zsto=zdt 
     653      clop='ave(only(x))' 
    676654#        endif 
    677       zout = nwritebio * zdt 
    678  
    679       ! Define indices of the horizontal output zoom and vertical limit storage 
     655      zout=nwritebio*zdt 
     656 
     657      ! Define indices of the horizontal output zoom and vertical limit storage      iimi = 1      ;      iima = jpi 
    680658      iimi = 1      ;      iima = jpi 
    681659      ijmi = 1      ;      ijma = jpj 
     
    683661 
    684662      ! define time axis 
    685       itmod = kt - nittrc000 + 1 
    686       it    = kt 
     663      it = kt - nittrc000 + 1 
    687664 
    688665      ! Define NETCDF files and fields at beginning of first time step 
     
    695672         ! Define the NETCDF files for biological trends 
    696673 
    697          CALL dia_nam(clhstnam,nwritebio,'biolog') 
     674         CALL dia_nam(clhstnam,nwrite,'biolog') 
    698675         IF(lwp)WRITE(numout,*) " Name of NETCDF file for biological trends ", clhstnam 
    699676         ! Horizontal grid : glamt and gphit 
    700          CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,      & 
     677         CALL histbeg(clhstnam, jpi, glamt, jpj, gphit,      & 
    701678            &    iimi, iima-iimi+1, ijmi, ijma-ijmi+1,          & 
    702             &    nittrc000-ndttrc, xjulian, zdt, nhoritb, nitb , domain_id=nidom ) 
     679            &    0, zjulian, rdt, nhoritb, nitb , domain_id=nidom) 
    703680         ! Vertical grid for biological trends 
    704          CALL histvert(nitb, 'deptht', 'Vertical T levels', 'm', ipk, gdept_0, ndepitb) 
     681         CALL histvert(nitb, 'deptht', 'Vertical T levels',  & 
     682            &    'm', ipk, gdept_0, ndepitb) 
    705683 
    706684         ! Declare all the output fields as NETCDF variables 
    707685         ! biological trends 
    708          DO jl = 1, jpdiabio 
    709             cltra  = ctrbio(jl)   ! short title for biological diagnostic 
    710             cltral = ctrbil(jl)   ! long title for biological diagnostic 
    711             cltrau = ctrbiu(jl)   ! UNIT for biological diagnostic 
    712             CALL histdef( nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  & 
     686         DO jn = 1, jpdiabio 
     687            cltra  = ctrbio(jn)   ! short title for biological diagnostic 
     688            cltral = ctrbil(jn)   ! long title for biological diagnostic 
     689            cltrau = ctrbiu(jn)   ! UNIT for biological diagnostic 
     690            CALL histdef(nitb, cltra, cltral, cltrau, jpi, jpj, nhoritb,  & 
    713691               &         ipk, 1, ipk,  ndepitb, 32, clop, zsto, zout) 
    714692         END DO 
    715693 
    716694         ! CLOSE netcdf Files 
    717           CALL histend( nitb ) 
     695          CALL histend(nitb) 
    718696 
    719697         IF(lwp) WRITE(numout,*) 
     
    727705 
    728706      ! biological trends 
    729       IF( lwp .AND. MOD( itmod, nwritebio ) == 0 ) THEN 
     707      IF( lwp .AND. MOD( kt, nwritebio ) == 0 ) THEN 
    730708         WRITE(numout,*) 'trcdit_wr : write NetCDF biological trends at ', kt, 'time-step' 
    731709         WRITE(numout,*) '~~~~~~ ' 
    732710      ENDIF 
    733711 
    734       DO jl = 1, jpdiabio 
    735          cltra = ctrbio(jl)  ! short title for biological diagnostic 
    736          CALL histwrite(nitb, cltra, it, trbio(:,:,:,jl), ndimt50,ndext50) 
     712      DO jn = 1, jpdiabio 
     713         cltra=ctrbio(jn)  ! short title for biological diagnostic 
     714         CALL histwrite(nitb, cltra, it, trbio(:,:,:,jn), ndimt50,ndext50) 
    737715      END DO 
     716 
     717      ! synchronise FILE 
     718      IF( MOD( kt, nwritebio ) == 0 .OR. kindic < 0 )   CALL histsync( nitb ) 
    738719 
    739720      ! Closing all files 
     
    741722      IF( kt == nitend .OR. kindic < 0 )   CALL histclo( nitb ) 
    742723      ! 
    743  
    744724   END SUBROUTINE trcdib_wr 
    745725 
     
    757737   !!---------------------------------------------------------------------- 
    758738CONTAINS 
    759    SUBROUTINE trc_dia( kt )                      ! Empty routine    
     739   SUBROUTINE trc_dia( kt )                      ! Empty routine 
    760740      INTEGER, INTENT(in) :: kt 
    761    END SUBROUTINE trc_dia    
     741   END SUBROUTINE trc_dia 
    762742 
    763743#endif 
  • branches/CMIP5_IPSL/NEMO/TOP_SRC/trcwri.F90

    r1656 r1830  
    11MODULE trcwri 
    2    !!====================================================================== 
     2   !!=================================================================================== 
    33   !!                       *** MODULE trcwri *** 
    4    !!    TOP :   Output of passive tracers  
    5    !!====================================================================== 
    6    !!             1.0  !   
    7    !!                  !  2009-05 (C. Ethe ) 
     4   !!    TOP :   Output of passive tracers 
     5   !!==================================================================================== 
     6   !! History :   1.0  !  2009-05 (C. Ethe)  Original code 
     7   !!                  !  2010-03 (C. Ethe, R. Seferian ) Add the tracer transport trends 
    88   !!---------------------------------------------------------------------- 
    99#if defined key_top &&  defined key_iomput 
     
    1111   !!   'key_top' && 'key_iomput'                              TOP models 
    1212   !!---------------------------------------------------------------------- 
    13    !! trc_wri     :  outputs of concentration fields 
    14    !!---------------------------------------------------------------------- 
     13   !! trc_wri_trc   :  outputs of concentration fields 
     14   !! trc_wri_trd   :  outputs of transport trends 
     15   !!---------------------------------------------------------------------- 
     16   USE dom_oce         ! ocean space and time domain variables 
     17   USE oce_trc 
     18   USE trp_trc 
    1519   USE trc 
     20   USE trdmld_trc_oce, ONLY : luttrd 
    1621   USE iom 
    1722#if defined key_off_tra 
     
    3540CONTAINS 
    3641 
    37    SUBROUTINE trc_wri( kt )   
     42   SUBROUTINE trc_wri( kt ) 
    3843      !!--------------------------------------------------------------------- 
    3944      !!                     ***  ROUTINE trc_wri  *** 
     45      !!  
     46      !! ** Purpose :   output passive tracers fields and dynamical trends 
     47      !!--------------------------------------------------------------------- 
     48      INTEGER, INTENT( in ) :: kt 
     49      !!--------------------------------------------------------------------- 
     50 
     51      ! 
     52      CALL iom_setkt  ( kt + ndttrc - 1 )       ! set the passive tracer time step 
     53      CALL trc_wri_trc( kt              )       ! outputs for tracer concentration 
     54      CALL trc_wri_trd( kt              )       ! outputs for dynamical trends 
     55      CALL iom_setkt  ( kt              )       ! set the model time step 
     56      ! 
     57   END SUBROUTINE trc_wri 
     58 
     59   SUBROUTINE trc_wri_trc( kt )   
     60      !!--------------------------------------------------------------------- 
     61      !!                     ***  ROUTINE trc_wri_trc  *** 
    4062      !! 
    4163      !! ** Purpose :   output passive tracers fields  
     
    4365      INTEGER, INTENT( in ) :: kt       ! ocean time-step 
    4466      INTEGER               :: jn 
    45       CHARACTER (len=20)    :: cltra 
     67      CHARACTER (len=20)    :: cltra, cltras 
    4668#if defined key_off_tra 
    4769      CHARACTER (len=40) :: clhstnam 
    4870      INTEGER ::   inum = 11            ! temporary logical unit 
    4971#endif 
    50  
     72#if defined key_diaar5  && defined key_pisces 
     73      INTEGER                      :: ji, jj, jk  ! dummy loop indices 
     74      REAL(wp)                     :: zoxy        ! oxygen concentration  
     75      REAL(wp), DIMENSION(jpi,jpj) :: zdic        ! DIC content  
     76      REAL(wp), DIMENSION(jpi,jpj) :: zo2min      ! O2 minimum concentration  
     77      REAL(wp), DIMENSION(jpi,jpj) :: zdepo2min   ! Depth of O2 minimum concentration  
     78#endif 
    5179      !!--------------------------------------------------------------------- 
    5280  
    53       ! Initialisation 
    54       ! -------------- 
    55  
    56       CALL iom_setkt( kt + ndttrc - 1 ) ! set the passive tracer time step 
    57  
    5881#if defined key_off_tra 
    5982      IF( kt == nittrc000 ) THEN 
     
    6790      ENDIF 
    6891#endif 
    69  
    70  
    7192      ! write the tracer concentrations in the file 
    7293      ! --------------------------------------- 
     
    7596         CALL iom_put( cltra, trn(:,:,:,jn) ) 
    7697      END DO 
    77       ! 
    78       CALL iom_setkt( kt )       ! set the model time step 
    79  
    80       ! 
    81    END SUBROUTINE trc_wri 
    82  
     98#if defined key_diaar5  && defined key_pisces 
     99      ! DIC content in kg/m2 
     100      zdic(:,:) = 0. 
     101      DO jk = 1, jpkm1 
     102         zdic(:,:) = zdic(:,:) + trn(:,:,jk,jpdic) * fse3t(:,:,jk) * tmask(:,:,jk) * 12.  
     103      ENDDO 
     104      ! Oxygen minimum concentration and depth 
     105      zo2min   (:,:) = trn(:,:,1,jpoxy) * tmask(:,:,1) 
     106      zdepo2min(:,:) = fsdepw(:,:,1)    * tmask(:,:,1) 
     107      DO jk = 2, jpkm1 
     108         DO jj = 1, jpj                
     109            DO ji = 1, jpi  
     110               IF( tmask(ji,jj,jk) == 1 ) then 
     111                  IF( trn(ji,jj,jk,jpoxy) < zo2min(ji,jj) ) then 
     112                     zo2min   (ji,jj) = trn(ji,jj,jk,jpoxy)  
     113                     zdepo2min(ji,jj) = fsdepw(ji,jj,jk) 
     114                  ENDIF 
     115               ENDIF 
     116            END DO 
     117         END DO 
     118      END DO 
     119      ! 
     120      CALL iom_put('INTDIC', zdic       )                              ! DIC content 
     121      CALL iom_put('O2MIN' , zo2min     )                              ! oxygen minimum concentration 
     122      CALL iom_put('ZO2MIN', zdepo2min  )                              ! depth of oxygen minimum concentration 
     123      CALL iom_put('PHYT'  , trn(:,:,:,jpphy) + trn(:,:,:,jpdia) )     ! total phytoplankton 
     124      CALL iom_put('ZOOT'  , trn(:,:,:,jpzoo) + trn(:,:,:,jpmes) )     ! total zooplankton 
     125      CALL iom_put('CHLT'  , trn(:,:,:,jpnch) + trn(:,:,:,jpdch) )     ! total chlorophyll 
     126      CALL iom_put('POCT'  , trn(:,:,:,jppoc) + trn(:,:,:,jpgoc) )     ! total carbon particles 
     127      CALL iom_put('PFET'  , trn(:,:,:,jpnfe) + trn(:,:,:,jpdfe) )     ! total biogenic iron 
     128      ! passive tracers at surface 
     129      DO jn = 1, jptra 
     130         cltras = TRIM(ctrcnm(jn))//'SFC'                   ! short title for tracer 
     131         CALL iom_put( cltras, trn(:,:,1,jn) ) 
     132      END DO 
     133      CALL iom_put('PHYTSFC',trn(:,:,1,jpphy) + trn(:,:,1,jpdia) ) 
     134      CALL iom_put('ZOOTSFC',trn(:,:,1,jpzoo) + trn(:,:,1,jpmes) ) 
     135      CALL iom_put('CHLTSFC',trn(:,:,1,jpnch) + trn(:,:,1,jpdch) ) 
     136      CALL iom_put('POCTSFC',trn(:,:,1,jppoc) + trn(:,:,1,jpgoc) ) 
     137      CALL iom_put('PFETSFC',trn(:,:,1,jpnfe) + trn(:,:,1,jpdfe) ) 
     138#endif 
     139      ! 
     140   END SUBROUTINE trc_wri_trc 
     141 
     142# if defined key_trc_diatrd 
     143 
     144   SUBROUTINE trc_wri_trd( kt ) 
     145      !!---------------------------------------------------------------------- 
     146      !!                     ***  ROUTINE trc_wri_trd  *** 
     147      !! 
     148      !! ** Purpose :   output of passive tracer : advection-diffusion trends 
     149      !! 
     150      !!---------------------------------------------------------------------- 
     151      INTEGER, INTENT( in ) ::   kt          ! ocean time-step 
     152      !! 
     153      CHARACTER (len=3) ::   cltra 
     154      INTEGER  ::   jn, jl, ikn 
     155      !!---------------------------------------------------------------------- 
     156 
     157      DO jn = 1, jptra 
     158         IF( luttrd(jn) ) THEN 
     159            ikn = ikeep(jn) 
     160            DO jl = 1, jpdiatrc 
     161               IF( jl == jptrc_xad ) WRITE (cltra,"(3a)") 'XAD' ! x advection for tracer 
     162               IF( jl == jptrc_yad ) WRITE (cltra,"(3a)") 'YAD'  ! y advection for tracer 
     163               IF( jl == jptrc_zad ) WRITE (cltra,"(3a)") 'ZAD'  ! z advection for tracer 
     164               IF( jl == jptrc_xdf ) WRITE (cltra,"(3a)") 'XDF'  ! x diffusion for tracer 
     165               IF( jl == jptrc_ydf ) WRITE (cltra,"(3a)") 'YDF'  ! y diffusion for tracer 
     166               IF( jl == jptrc_zdf ) WRITE (cltra,"(3a)") 'ZDF'  ! z diffusion for tracer 
     167# if defined key_trcldf_eiv 
     168               IF( jl == jptrc_xei ) WRITE (cltra,"(3a)") 'XGV'  ! x gent velocity for tracer 
     169               IF( jl == jptrc_yei ) WRITE (cltra,"(3a)") 'YGV'  ! y gent velocity for tracer 
     170               IF( jl == jptrc_zei ) WRITE (cltra,"(3a)") 'ZGV'  ! z gent velocity for tracer 
     171# endif 
     172# if defined key_trcdmp 
     173               IF( jl == jptrc_dmp ) WRITE (cltra,"(3a)") 'DMP'  ! damping 
     174# endif 
     175               IF( jl == jptrc_sbc ) WRITE (cltra,"(3a)") 'SBC'  ! surface boundary conditions 
     176               ! write the trends 
     177               CALL iom_put( cltra, trtrd(:,:,:,ikn,jl) ) 
     178            END DO 
     179         END IF 
     180      END DO 
     181      ! 
     182   END SUBROUTINE trc_wri_trd 
     183 
     184# else 
     185   SUBROUTINE trc_wri_trd( kt )                      ! Dummy routine 
     186      INTEGER, INTENT ( in ) ::   kt 
     187   END SUBROUTINE trc_wri_trd 
     188#endif 
    83189#else 
    84190   !!---------------------------------------------------------------------- 
     
    90196   INTEGER, INTENT(in) :: kt 
    91197   END SUBROUTINE trc_wri 
    92  
    93198#endif 
    94199 
Note: See TracChangeset for help on using the changeset viewer.