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

Changeset 8104


Ignore:
Timestamp:
2017-05-31T12:06:35+02:00 (7 years ago)
Author:
davestorkey
Message:

UKMO dev_r5518_GO6_package branch: update to tracer trends diagnostics. Corresponds to update at revision 8102 in 3.6_stable branch.

  1. Correct bugs in calculation of total trends and trends due to vertical diffusion.
  2. Output component trends every second timestep so that sum of component trends plus Asselin filter trend equals total trend.
  3. Layer-integrated versions of trends (as per CMIP6 definition) available in field_def.xml.
Location:
branches/UKMO/dev_r5518_GO6_package/NEMOGCM
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/CONFIG/SHARED/field_def.xml

    r8008 r8104  
    784784    --> 
    785785 
    786     <field_group id="trendT" grid_ref="grid_T_3D"> 
    787786      <!-- variables available with ln_tra_trd --> 
    788       <field id="ttrd_xad"      long_name="temperature-trend: i-advection"                                                                                          unit="degC/s"                        /> 
     787  
     788     <!-- Asselin trends  calculated on odd time steps--> 
     789     <field_group id="trendT_odd"  grid_ref="grid_T_3D"> 
     790      <field id="ttrd_atf"      long_name="temperature-trend: asselin time filter"       unit="degree_C/s" /> 
     791      <field id="strd_atf"      long_name="salinity   -trend: asselin time filter"       unit="0.001/s" /> 
     792      <!-- Thickness weighted versions: --> 
     793     <field id="ttrd_atf_e3t"      unit="degC/s * m"  >  ttrd_atf * e3t </field> 
     794      <field id="strd_atf_e3t"      unit="1e-3/s * m"  >  strd_atf * e3t </field> 
     795      <!-- OMIP  layer-integrated trends --> 
     796      <field id="ttrd_atf_li"      long_name="layer integrated heat-trend: asselin time filter "       unit="W/m^2" > ttrd_atf_e3t * 1026.0 * 3991.86795711963  </field> 
     797       <field id="strd_atf_li"      long_name="layer integrated salt   -trend: asselin time filter "       unit="kg/(m^2 s)" > strd_atf_e3t * 1026.0 * 0.001 </field> 
     798      </field_group> 
     799 
     800    <!-- Other trends  calculated on even time steps--> 
     801  <field_group id="trendT_even" grid_ref="grid_T_3D"> 
     802       <field id="ttrd_xad"      long_name="temperature-trend: i-advection"                                                                                          unit="degC/s"                        /> 
    789803      <field id="strd_xad"      long_name="salinity   -trend: i-advection"                                                                                          unit="1e-3/s"                        /> 
    790804      <field id="ttrd_yad"      long_name="temperature-trend: j-advection"                                                                                          unit="degC/s"                        /> 
     
    830844      <field id="ttrd_qsr"      long_name="temperature-trend: solar penetr. heating"     unit="degree_C/s" /> 
    831845      <field id="ttrd_bbc"      long_name="temperature-trend: geothermal heating"        unit="degree_C/s" /> 
    832       <field id="ttrd_atf"      long_name="temperature-trend: asselin time filter"       unit="degree_C/s" /> 
    833       <field id="strd_atf"      long_name="salinity   -trend: asselin time filter"       unit="0.001/s" /> 
    834       <field id="ttrd_tot"      long_name="temperature-trend: total model trend"         unit="degC/s" /> 
    835       <field id="strd_tot"      long_name="salinity   -trend: total model trend"         unit="1e-3/s" /> 
    836  
     846  
    837847      <!-- Thickness weighted versions: --> 
    838848      <field id="ttrd_xad_e3t"      unit="degC/s * m" >  ttrd_xad * e3t </field> 
     
    853863      <field id="strd_evd_e3t"      unit="1e-3/s * m" >  strd_evd * e3t </field> 
    854864 
     865      <field id="strd_evd_e3t"      unit="1e-3/s * m" >  strd_evd * e3t </field> 
     866 
    855867      <!-- ln_traldf_iso=T only (iso-neutral diffusion) --> 
    856868      <field id="ttrd_iso_x_e3t"    unit="degC/s * m"  >  ttrd_iso_x * e3t </field> 
     
    876888      <field id="ttrd_qsr_e3t"      unit="degC/s * m"  >  ttrd_qsr * e3t </field> 
    877889      <field id="ttrd_bbc_e3t"      unit="degC/s * m"  >  ttrd_bbc * e3t </field> 
    878       <field id="ttrd_atf_e3t"      unit="degC/s * m"  >  ttrd_atf * e3t </field> 
    879       <field id="strd_atf_e3t"      unit="1e-3/s * m"  >  strd_atf * e3t </field> 
     890 
     891      <!-- OMIP  layer-integrated trends --> 
     892      <field id="ttrd_totad_li"    long_name="layer integrated heat-trend : total advection"       unit="W/m^2"     > ttrd_totad_e3t * 1026.0 * 3991.86795711963 </field> 
     893      <field id="strd_totad_li"    long_name="layer integrated salt   -trend : total advection"      unit="kg/(m^2 s)"    > strd_totad_e3t * 1026.0 * 0.001  </field> 
     894      <field id="ttrd_evd_li"      long_name="layer integrated heat-trend : EVD convection"         unit="W/m^2"    > ttrd_evd_e3t * 1026.0 * 3991.86795711963 </field> 
     895      <field id="strd_evd_li"      long_name="layer integrated salt   -trend : EVD convection"      unit="kg/(m^2 s)"  > strd_evd_e3t * 1026.0 * 0.001  </field> 
     896      <field id="ttrd_iso_li"      long_name="layer integrated heat-trend : isopycnal diffusion"    unit="W/m^2" > ttrd_iso_e3t * 1026.0 * 3991.86795711963 </field> 
     897      <field id="strd_iso_li"      long_name="layer integrated salt   -trend : isopycnal diffusion"   unit="kg/(m^2 s)" > strd_iso_e3t * 1026.0 * 0.001  </field> 
     898      <field id="ttrd_zdfp_li"     long_name="layer integrated heat-trend : pure vert. diffusion"   unit="W/m^2" > ttrd_zdfp_e3t * 1026.0 * 3991.86795711963 </field> 
     899      <field id="strd_zdfp_li"     long_name="layer integrated salt   -trend : pure vert. diffusion"   unit="kg/(m^2 s)" > strd_zdfp_e3t * 1026.0 * 0.001  </field> 
     900      <field id="ttrd_qns_li"      long_name="layer integrated heat-trend : non-solar flux + runoff"   unit="W/m^2" grid_ref="grid_T_2D"> ttrd_qns_e3t * 1026.0 * 3991.86795711963 </field> 
     901      <field id="ttrd_qsr_li"      long_name="layer integrated heat-trend : solar flux"   unit="W/m^2"  grid_ref="grid_T_3D"> ttrd_qsr_e3t * 1026.0 * 3991.86795711963 </field> 
     902      <field id="ttrd_bbl_li"      long_name="layer integrated heat-trend: bottom boundary layer "     unit="W/m^2" > ttrd_bbl_e3t * 1026.0 * 3991.86795711963 </field> 
     903      <field id="strd_bbl_li"      long_name="layer integrated salt   -trend: bottom boundary layer "     unit="kg/(m^2 s)" > strd_bbl_e3t * 1026.0 * 0.001  </field> 
     904      <field id="ttrd_evd_li"      long_name="layer integrated heat -trend: evd convection "       unit="W/m^2" >ttrd_evd_e3t * 1026.0 * 3991.86795711963  </field> 
     905      <field id="strd_evd_li"      long_name="layer integrated salt -trend: evd convection "       unit="kg/(m^2 s)" > strd_evd_e3t * 1026.0 * 0.001  </field> 
     906     </field_group> 
     907    
     908     <!--  Total trends calculated every time step--> 
     909     <field_group id="trendT" grid_ref="grid_T_3D"> 
     910      <field id="ttrd_tot"      long_name="temperature-trend: total model trend"         unit="degC/s" /> 
     911      <field id="strd_tot"      long_name="salinity   -trend: total model trend"         unit="1e-3/s" /> 
     912      <!-- Thickness weighted versions: --> 
    880913      <field id="ttrd_tot_e3t"      unit="degC/s * m"  >  ttrd_tot * e3t </field> 
    881914      <field id="strd_tot_e3t"      unit="1e-3/s * m"  >  strd_tot * e3t </field> 
    882  
     915      <!-- OMIP  layer-integrated total trends --> 
     916      <field id="ttrd_tot_li"      long_name="layer integrated heat-trend: total model trend :"         unit="W/m^2" > ttrd_tot_e3t * 1026.0 * 3991.86795711963 </field> 
     917      <field id="strd_tot_li"      long_name="layer integrated salt   -trend: total model trend :"         unit="kg/(m^2 s)" > strd_tot_e3t * 1026.0 * 0.001  </field> 
     918    
     919      <!-- **** these trends have not been apportioned to all/even/odd ts yet **** --> 
    883920      <!-- variables available with ln_KE_trd --> 
    884921      <field id="ketrd_hpg"     long_name="ke-trend: hydrostatic pressure gradient"          unit="W/s^3"                        /> 
     
    9781015    --> 
    9791016 
     1017     <field_group id="TRD" > 
     1018          <field field_ref="ttrd_totad_li"   name="opottempadvect"  /> 
     1019          <field field_ref="ttrd_iso_li"     name="opottemppmdiff"  /> 
     1020          <field field_ref="ttrd_zdfp_li"    name="opottempdiff"  /> 
     1021          <field field_ref="ttrd_evd_li"     name="opottempevd" /> 
     1022          <field field_ref="strd_evd_li"     name="osaltevd" /> 
     1023          <field field_ref="ttrd_qns_li"     name="opottempqns"  /> 
     1024          <field field_ref="ttrd_qsr_li"     name="rsdoabsorb" operation="accumulate" /> 
     1025          <field field_ref="strd_totad_li"   name="osaltadvect" /> 
     1026          <field field_ref="strd_iso_li"     name="osaltpmdiff"  /> 
     1027          <field field_ref="strd_zdfp_li"    name="osaltdiff" /> 
     1028    </field_group> 
     1029     
    9801030    <field_group id="mooring" > 
    9811031      <field field_ref="toce"         name="thetao"   long_name="sea_water_potential_temperature"      /> 
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r7750 r8104  
    16271627#if ! defined key_xios2 
    16281628      WRITE(cl1,'(i1)')        1   ;   CALL iom_set_field_attr('field_definition', freq_op=cl1//'ts', freq_offset='0ts') 
     1629      WRITE(cl1,'(i1)')        2   ;   CALL iom_set_field_attr('trendT_even'      , freq_op=cl1//'ts', freq_offset='0ts') 
     1630      WRITE(cl1,'(i1)')        2   ;   CALL iom_set_field_attr('trendT_odd'       , freq_op=cl1//'ts', freq_offset='-1ts') 
    16291631      WRITE(cl1,'(i1)')  nn_fsbc   ;   CALL iom_set_field_attr('SBC'             , freq_op=cl1//'ts', freq_offset='0ts') 
    16301632      WRITE(cl1,'(i1)')  nn_fsbc   ;   CALL iom_set_field_attr('SBC_scalar'      , freq_op=cl1//'ts', freq_offset='0ts') 
     
    16331635#else 
    16341636      f_op%timestep = 1        ;  f_of%timestep = 0  ; CALL iom_set_field_attr('field_definition', freq_op=f_op, freq_offset=f_of) 
     1637      f_op%timestep = 2        ;  f_of%timestep = 0  ; CALL iom_set_field_attr('trendT_even'      , freq_op=f_op, freq_offset=f_of) 
     1638      f_op%timestep = 2        ;  f_of%timestep = -1 ; CALL iom_set_field_attr('trendT_odd'       , freq_op=f_op, freq_offset=f_of) 
    16351639      f_op%timestep = nn_fsbc  ;  f_of%timestep = 0  ; CALL iom_set_field_attr('SBC'             , freq_op=f_op, freq_offset=f_of) 
    16361640      f_op%timestep = nn_fsbc  ;  f_of%timestep = 0  ; CALL iom_set_field_attr('SBC_scalar'      , freq_op=f_op, freq_offset=f_of) 
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/TRA/tranxt.F90

    r7573 r8104  
    135135            CALL trd_tra( kt, 'TRA', jp_sal, jptra_zdfp, ztrds ) 
    136136         ENDIF 
    137          ! total trend for the non-time-filtered variables.  
    138          DO jk = 1, jpkm1 
    139             zfact = 1.0 / rdttra(jk) 
    140             ztrdt(:,:,jk) = ( tsa(:,:,jk,jp_tem) - tsn(:,:,jk,jp_tem) ) * zfact  
    141             ztrds(:,:,jk) = ( tsa(:,:,jk,jp_sal) - tsn(:,:,jk,jp_sal) ) * zfact  
    142          END DO 
     137         ! total trend for the non-time-filtered variables. 
     138         ! G Nurser 23 Mar 2017. Recalculate trend as Delta(e3t*T)/e3tn; e3tn cancel from tsn terms 
     139         IF( lk_vvl ) THEN 
     140            DO jk = 1, jpkm1 
     141               zfact = 1.0 / rdttra(jk) 
     142               ztrdt(:,:,jk) = ( tsa(:,:,jk,jp_tem)*fse3t_a(:,:,jk) / fse3t_n(:,:,jk) - tsn(:,:,jk,jp_tem)) * zfact 
     143               ztrds(:,:,jk) = ( tsa(:,:,jk,jp_sal)*fse3t_a(:,:,jk) / fse3t_n(:,:,jk) - tsn(:,:,jk,jp_sal)) * zfact 
     144            END DO 
     145         ELSE 
     146            DO jk = 1, jpkm1 
     147               zfact = 1.0 / rdttra(jk) 
     148               ztrdt(:,:,jk) = ( tsa(:,:,jk,jp_tem) - tsn(:,:,jk,jp_tem) ) * zfact  
     149               ztrds(:,:,jk) = ( tsa(:,:,jk,jp_sal) - tsn(:,:,jk,jp_sal) ) * zfact  
     150            END DO 
     151         END IF 
    143152         CALL trd_tra( kt, 'TRA', jp_tem, jptra_tot, ztrdt ) 
    144153         CALL trd_tra( kt, 'TRA', jp_sal, jptra_tot, ztrds ) 
    145          ! Store now fields before applying the Asselin filter  
    146          ! in order to calculate Asselin filter trend later. 
    147          ztrdt(:,:,:) = tsn(:,:,:,jp_tem)  
    148          ztrds(:,:,:) = tsn(:,:,:,jp_sal) 
     154         IF( .NOT.lk_vvl )  THEN 
     155            ! Store now fields before applying the Asselin filter  
     156            ! in order to calculate Asselin filter trend later. 
     157            ztrdt(:,:,:) = tsn(:,:,:,jp_tem)  
     158            ztrds(:,:,:) = tsn(:,:,:,jp_sal) 
     159         END IF 
    149160      ENDIF 
    150161 
     
    155166            END DO 
    156167         END DO 
     168         IF (l_trdtra.AND.lk_vvl) THEN      ! Zero Asselin filter contribution must be explicitly written out since for vvl 
     169                                            ! Asselin filter is output by tra_nxt_vvl that is not called on this time step 
     170            ztrdt(:,:,:) = 0._wp 
     171            ztrds(:,:,:) = 0._wp 
     172            CALL trd_tra( kt, 'TRA', jp_tem, jptra_atf, ztrdt ) 
     173            CALL trd_tra( kt, 'TRA', jp_sal, jptra_atf, ztrds ) 
     174         END IF 
    157175      ELSE                                            ! Leap-Frog + Asselin filter time stepping 
    158176         ! 
     
    164182      ! 
    165183     ! trends computation 
    166       IF( l_trdtra ) THEN      ! trend of the Asselin filter (tb filtered - tb)/dt      
     184      IF( l_trdtra.AND..NOT.lk_vvl) THEN      ! trend of the Asselin filter (tb filtered - tb)/dt      
    167185         DO jk = 1, jpkm1 
    168186            zfact = 1._wp / r2dtra(jk)              
     
    172190         CALL trd_tra( kt, 'TRA', jp_tem, jptra_atf, ztrdt ) 
    173191         CALL trd_tra( kt, 'TRA', jp_sal, jptra_atf, ztrds ) 
    174          CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds ) 
    175192      END IF 
     193      IF( l_trdtra) CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds ) 
    176194      ! 
    177195      !                        ! control print 
     
    289307      LOGICAL  ::   ll_tra_hpg, ll_traqsr, ll_rnf, ll_isf   ! local logical 
    290308      INTEGER  ::   ji, jj, jk, jn              ! dummy loop indices 
    291       REAL(wp) ::   zfact1, ztc_a , ztc_n , ztc_b , ztc_f , ztc_d    ! local scalar 
     309      REAL(wp) ::   zfact, zfact1, ztc_a , ztc_n , ztc_b , ztc_f , ztc_d    ! local scalar 
    292310      REAL(wp) ::   zfact2, ze3t_b, ze3t_n, ze3t_a, ze3t_f, ze3t_d   !   -      - 
     311      REAL(wp), POINTER, DIMENSION(:,:,:,:) :: ztrd_atf 
    293312      !!---------------------------------------------------------------------- 
    294313      ! 
     
    315334      ENDIF 
    316335      ! 
     336      IF( l_trdtra )   THEN 
     337         CALL wrk_alloc( jpi, jpj, jpk, kjpt, ztrd_atf ) 
     338         ztrd_atf(:,:,:,:) = 0.0_wp 
     339      ENDIF 
    317340      DO jn = 1, kjpt       
    318341         DO jk = 1, jpkm1 
     342            zfact = 1._wp / r2dtra(jk) 
    319343            zfact1 = atfp * p2dt(jk) 
    320344            zfact2 = zfact1 / rau0 
     
    371395                     pta(ji,jj,jk,jn) = ze3t_d * ( ztc_n  + rbcp * ztc_d  )   ! ta <-- Brown & Campana average 
    372396                  ENDIF 
     397                  IF( l_trdtra ) THEN 
     398                     ztrd_atf(ji,jj,jk,jn) = (ztc_f - ztc_n) * zfact/ze3t_n 
     399                  ENDIF 
    373400               END DO 
    374401            END DO 
     
    377404      END DO 
    378405      ! 
     406      IF( l_trdtra ) THEN 
     407         CALL trd_tra( kt, 'TRA', jp_tem, jptra_atf, ztrd_atf(:,:,:,jp_tem) ) 
     408         CALL trd_tra( kt, 'TRA', jp_sal, jptra_atf, ztrd_atf(:,:,:,jp_sal) ) 
     409         CALL wrk_dealloc( jpi, jpj, jpk, kjpt, ztrd_atf ) 
     410      ENDIF 
     411 
    379412   END SUBROUTINE tra_nxt_vvl 
    380413 
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/TRA/trazdf.F90

    r6486 r8104  
    9494 
    9595      IF( l_trdtra )   THEN                      ! save the vertical diffusive trends for further diagnostics 
    96          DO jk = 1, jpkm1 
    97             ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dtra(jk) ) - ztrdt(:,:,jk) 
    98             ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dtra(jk) ) - ztrds(:,:,jk) 
    99          END DO 
     96         ! G Nurser 23 Mar 2017. Recalculate trend as Delta(e3t*T)/e3tn. 
     97         IF( lk_vvl ) THEN 
     98            DO jk = 1, jpkm1 
     99               ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem)*fse3t_a(:,:,jk) - tsb(:,:,jk,jp_tem)*fse3t_b(:,:,jk) ) & 
     100                    & / (fse3t_n(:,:,jk)*r2dtra(jk)) ) - ztrdt(:,:,jk) 
     101               ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal)*fse3t_a(:,:,jk) - tsb(:,:,jk,jp_sal)*fse3t_b(:,:,jk) ) & 
     102                    & / (fse3t_n(:,:,jk)*r2dtra(jk)) ) - ztrds(:,:,jk) 
     103            END DO 
     104         ELSE 
     105            DO jk = 1, jpkm1 
     106               ztrdt(:,:,jk) = ( ( tsa(:,:,jk,jp_tem) - tsb(:,:,jk,jp_tem) ) / r2dtra(jk) ) - ztrdt(:,:,jk) 
     107               ztrds(:,:,jk) = ( ( tsa(:,:,jk,jp_sal) - tsb(:,:,jk,jp_sal) ) / r2dtra(jk) ) - ztrds(:,:,jk) 
     108            END DO 
     109         END IF 
    100110         CALL lbc_lnk( ztrdt, 'T', 1. ) 
    101111         CALL lbc_lnk( ztrds, 'T', 1. ) 
  • branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/OPA_SRC/TRD/trdtra.F90

    r7554 r8104  
    301301      !! ** Purpose :   output 3D tracer trends using IOM 
    302302      !!---------------------------------------------------------------------- 
    303       REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdx   ! Temperature or U trend  
    304       REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdy   ! Salinity    or V trend 
    305       INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index 
    306       INTEGER                   , INTENT(in   ) ::   kt      ! time step 
    307       !! 
    308       INTEGER ::   ji, jj, jk   ! dummy loop indices 
    309       INTEGER ::   ikbu, ikbv   ! local integers 
    310       REAL(wp), POINTER, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace  
    311       !!---------------------------------------------------------------------- 
    312       ! 
    313 !!gm Rq: mask the trends already masked in trd_tra, but lbc_lnk should probably be added 
    314       ! 
    315       SELECT CASE( ktrd ) 
    316       CASE( jptra_xad  )   ;   CALL iom_put( "ttrd_xad" , ptrdx )        ! x- horizontal advection 
    317                                CALL iom_put( "strd_xad" , ptrdy ) 
    318       CASE( jptra_yad  )   ;   CALL iom_put( "ttrd_yad" , ptrdx )        ! y- horizontal advection 
    319                                CALL iom_put( "strd_yad" , ptrdy ) 
    320       CASE( jptra_zad  )   ;   CALL iom_put( "ttrd_zad" , ptrdx )        ! z- vertical   advection 
    321                                CALL iom_put( "strd_zad" , ptrdy ) 
    322                                IF( .NOT. lk_vvl ) THEN                   ! cst volume : adv flux through z=0 surface 
    323                                   CALL wrk_alloc( jpi, jpj, z2dx, z2dy ) 
    324                                   z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / fse3t(:,:,1) 
    325                                   z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / fse3t(:,:,1) 
    326                                   CALL iom_put( "ttrd_sad", z2dx ) 
    327                                   CALL iom_put( "strd_sad", z2dy ) 
    328                                   CALL wrk_dealloc( jpi, jpj, z2dx, z2dy ) 
    329                                ENDIF 
    330       CASE( jptra_totad  ) ;   CALL iom_put( "ttrd_totad" , ptrdx )        ! total   advection 
    331                                CALL iom_put( "strd_totad" , ptrdy ) 
    332       CASE( jptra_ldf  )   ;   CALL iom_put( "ttrd_ldf" , ptrdx )        ! lateral diffusion 
    333                                CALL iom_put( "strd_ldf" , ptrdy ) 
    334       CASE( jptra_zdf  )   ;   CALL iom_put( "ttrd_zdf" , ptrdx )        ! vertical diffusion (including Kz contribution) 
    335                                CALL iom_put( "strd_zdf" , ptrdy ) 
    336       CASE( jptra_zdfp )   ;   CALL iom_put( "ttrd_zdfp", ptrdx )        ! PURE vertical diffusion (no isoneutral contribution) 
    337                                CALL iom_put( "strd_zdfp", ptrdy ) 
    338       CASE( jptra_evd )    ;   CALL iom_put( "ttrd_evd", ptrdx )         ! EVD trend (convection) 
    339                                CALL iom_put( "strd_evd", ptrdy ) 
    340       CASE( jptra_iso_x )  ;   CALL iom_put( "ttrd_iso_x", ptrdx )       ! x-component of isopycnal mixing 
    341                                CALL iom_put( "strd_iso_x", ptrdy ) 
    342       CASE( jptra_iso_y )  ;   CALL iom_put( "ttrd_iso_y", ptrdx )       ! y-component of isopycnal mixing 
    343                                CALL iom_put( "strd_iso_y", ptrdy ) 
    344       CASE( jptra_iso_z1 ) ;   CALL iom_put( "ttrd_iso_z1", ptrdx )      ! first part of z-component of isopycnal mixing 
    345                                CALL iom_put( "strd_iso_z1", ptrdy ) 
    346       CASE( jptra_dmp  )   ;   CALL iom_put( "ttrd_dmp" , ptrdx )        ! internal restoring (damping) 
    347                                CALL iom_put( "strd_dmp" , ptrdy ) 
    348       CASE( jptra_bbl  )   ;   CALL iom_put( "ttrd_bbl" , ptrdx )        ! bottom boundary layer 
    349                                CALL iom_put( "strd_bbl" , ptrdy ) 
    350       CASE( jptra_npc  )   ;   CALL iom_put( "ttrd_npc" , ptrdx )        ! static instability mixing 
    351                                CALL iom_put( "strd_npc" , ptrdy ) 
    352       CASE( jptra_nsr  )   ;   CALL iom_put( "ttrd_qns" , ptrdx(:,:,1) )        ! surface forcing + runoff (ln_rnf=T) 
    353                                CALL iom_put( "strd_cdt" , ptrdy(:,:,1) )        ! output as 2D surface fields 
    354       CASE( jptra_qsr  )   ;   CALL iom_put( "ttrd_qsr" , ptrdx )        ! penetrative solar radiat. (only on temperature) 
    355       CASE( jptra_bbc  )   ;   CALL iom_put( "ttrd_bbc" , ptrdx )        ! geothermal heating   (only on temperature) 
    356       CASE( jptra_atf  )   ;   CALL iom_put( "ttrd_atf" , ptrdx )        ! asselin time Filter 
    357                                CALL iom_put( "strd_atf" , ptrdy ) 
    358       CASE( jptra_tot  )   ;   CALL iom_put( "ttrd_tot" , ptrdx )        ! model total trend 
    359                                CALL iom_put( "strd_tot" , ptrdy ) 
    360       END SELECT 
    361       ! 
     303     REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdx   ! Temperature or U trend  
     304     REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdy   ! Salinity    or V trend 
     305     INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index 
     306     INTEGER                   , INTENT(in   ) ::   kt      ! time step 
     307     !! 
     308     INTEGER ::   ji, jj, jk   ! dummy loop indices 
     309     INTEGER ::   ikbu, ikbv   ! local integers 
     310     REAL(wp), POINTER, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace  
     311     !!---------------------------------------------------------------------- 
     312     ! 
     313     !!gm Rq: mask the trends already masked in trd_tra, but lbc_lnk should probably be added 
     314     ! 
     315     ! Trends evaluated every time step that could go to the standard T file and can be output every ts into a 1ts file if 1ts output is selected 
     316     SELECT CASE( ktrd ) 
     317     ! This total trend is done every time step 
     318     CASE( jptra_tot  )   ;   CALL iom_put( "ttrd_tot" , ptrdx )           ! model total trend 
     319        CALL iom_put( "strd_tot" , ptrdy ) 
     320     END SELECT 
     321 
     322     ! These trends are done every second time step. When 1ts output is selected must go different (2ts) file from standard T-file 
     323     IF( MOD( kt, 2 ) == 0 ) THEN 
     324        SELECT CASE( ktrd ) 
     325        CASE( jptra_xad  )   ;   CALL iom_put( "ttrd_xad" , ptrdx )        ! x- horizontal advection 
     326           CALL iom_put( "strd_xad" , ptrdy ) 
     327        CASE( jptra_yad  )   ;   CALL iom_put( "ttrd_yad" , ptrdx )        ! y- horizontal advection 
     328           CALL iom_put( "strd_yad" , ptrdy ) 
     329        CASE( jptra_zad  )   ;   CALL iom_put( "ttrd_zad" , ptrdx )        ! z- vertical   advection 
     330           CALL iom_put( "strd_zad" , ptrdy ) 
     331           IF( .NOT. lk_vvl ) THEN                   ! cst volume : adv flux through z=0 surface 
     332              CALL wrk_alloc( jpi, jpj, z2dx, z2dy ) 
     333              z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / fse3t(:,:,1) 
     334              z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / fse3t(:,:,1) 
     335              CALL iom_put( "ttrd_sad", z2dx ) 
     336              CALL iom_put( "strd_sad", z2dy ) 
     337              CALL wrk_dealloc( jpi, jpj, z2dx, z2dy ) 
     338           ENDIF 
     339        CASE( jptra_totad  ) ;   CALL iom_put( "ttrd_totad" , ptrdx )      ! total   advection 
     340           CALL iom_put( "strd_totad" , ptrdy ) 
     341        CASE( jptra_ldf  )   ;   CALL iom_put( "ttrd_ldf" , ptrdx )        ! lateral diffusion 
     342           CALL iom_put( "strd_ldf" , ptrdy ) 
     343        CASE( jptra_zdf  )   ;   CALL iom_put( "ttrd_zdf" , ptrdx )        ! vertical diffusion (including Kz contribution) 
     344           CALL iom_put( "strd_zdf" , ptrdy ) 
     345        CASE( jptra_zdfp )   ;   CALL iom_put( "ttrd_zdfp", ptrdx )        ! PURE vertical diffusion (no isoneutral contribution) 
     346           CALL iom_put( "strd_zdfp", ptrdy ) 
     347        CASE( jptra_evd )    ;   CALL iom_put( "ttrd_evd", ptrdx )         ! EVD trend (convection) 
     348           CALL iom_put( "strd_evd", ptrdy ) 
     349        CASE( jptra_dmp  )   ;   CALL iom_put( "ttrd_dmp" , ptrdx )        ! internal restoring (damping) 
     350           CALL iom_put( "strd_dmp" , ptrdy ) 
     351        CASE( jptra_bbl  )   ;   CALL iom_put( "ttrd_bbl" , ptrdx )        ! bottom boundary layer 
     352           CALL iom_put( "strd_bbl" , ptrdy ) 
     353        CASE( jptra_npc  )   ;   CALL iom_put( "ttrd_npc" , ptrdx )        ! static instability mixing 
     354           CALL iom_put( "strd_npc" , ptrdy ) 
     355        CASE( jptra_bbc  )   ;   CALL iom_put( "ttrd_bbc" , ptrdx )        ! geothermal heating   (only on temperature) 
     356        CASE( jptra_nsr  )   ;   CALL iom_put( "ttrd_qns" , ptrdx(:,:,1) ) ! surface forcing + runoff (ln_rnf=T) 
     357           CALL iom_put( "strd_cdt" , ptrdy(:,:,1) )        ! output as 2D surface fields 
     358        CASE( jptra_qsr  )   ;   CALL iom_put( "ttrd_qsr" , ptrdx )        ! penetrative solar radiat. (only on temperature) 
     359        END SELECT 
     360        ! the Asselin filter trend  is also every other time step but needs to be lagged one time step 
     361        ! Even when 1ts output is selected can go to the same (2ts) file as the trends plotted every even time step. 
     362     ELSE IF( MOD( kt, 2 ) == 1 ) THEN 
     363        SELECT CASE( ktrd ) 
     364        CASE( jptra_atf  )   ;   CALL iom_put( "ttrd_atf" , ptrdx )        ! asselin time Filter 
     365           CALL iom_put( "strd_atf" , ptrdy ) 
     366        END SELECT 
     367     END IF 
     368     ! 
    362369   END SUBROUTINE trd_tra_iom 
    363370 
Note: See TracChangeset for help on using the changeset viewer.