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 9817 for branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

Ignore:
Timestamp:
2018-06-21T11:58:42+02:00 (6 years ago)
Author:
dancopsey
Message:

Merged in GO6 package branch up to revision 8356.

Location:
branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD/trd_oce.F90

    r9816 r9817  
    3333# endif 
    3434   !                                                  !!!* Active tracers trends indexes 
    35    INTEGER, PUBLIC, PARAMETER ::   jptot_tra  = 14     !: Total trend nb: change it when adding/removing one indice below 
     35   INTEGER, PUBLIC, PARAMETER ::   jptot_tra  = 20     !: Total trend nb: change it when adding/removing one indice below 
    3636   !                               ===============     !   
    3737   INTEGER, PUBLIC, PARAMETER ::   jptra_xad  =  1     !: x- horizontal advection 
     
    3939   INTEGER, PUBLIC, PARAMETER ::   jptra_zad  =  3     !: z- vertical   advection 
    4040   INTEGER, PUBLIC, PARAMETER ::   jptra_sad  =  4     !: z- vertical   advection 
    41    INTEGER, PUBLIC, PARAMETER ::   jptra_ldf  =  5     !: lateral       diffusion 
    42    INTEGER, PUBLIC, PARAMETER ::   jptra_zdf  =  6     !: vertical      diffusion 
    43    INTEGER, PUBLIC, PARAMETER ::   jptra_zdfp =  7     !: "PURE" vert.  diffusion (ln_traldf_iso=T) 
    44    INTEGER, PUBLIC, PARAMETER ::   jptra_bbc  =  8     !: Bottom Boundary Condition (geoth. heating)  
    45    INTEGER, PUBLIC, PARAMETER ::   jptra_bbl  =  9     !: Bottom Boundary Layer (diffusive and/or advective) 
    46    INTEGER, PUBLIC, PARAMETER ::   jptra_npc  = 10     !: non-penetrative convection treatment 
    47    INTEGER, PUBLIC, PARAMETER ::   jptra_dmp  = 11     !: internal restoring (damping) 
    48    INTEGER, PUBLIC, PARAMETER ::   jptra_qsr  = 12     !: penetrative solar radiation 
    49    INTEGER, PUBLIC, PARAMETER ::   jptra_nsr  = 13     !: non solar radiation / C/D on salinity  (+runoff if ln_rnf=T) 
    50    INTEGER, PUBLIC, PARAMETER ::   jptra_atf  = 14     !: Asselin time filter 
     41   INTEGER, PUBLIC, PARAMETER ::   jptra_totad  =  5   !: total         advection 
     42   INTEGER, PUBLIC, PARAMETER ::   jptra_ldf  =  6     !: lateral       diffusion 
     43   INTEGER, PUBLIC, PARAMETER ::   jptra_iso_x  =  7   !: x-component of isopycnal diffusion 
     44   INTEGER, PUBLIC, PARAMETER ::   jptra_iso_y  =  8   !: y-component of isopycnal diffusion 
     45   INTEGER, PUBLIC, PARAMETER ::   jptra_iso_z1 =  9   !: z-component of isopycnal diffusion 
     46   INTEGER, PUBLIC, PARAMETER ::   jptra_zdf  = 10     !: vertical      diffusion 
     47   INTEGER, PUBLIC, PARAMETER ::   jptra_zdfp = 11     !: "PURE" vert.  diffusion (ln_traldf_iso=T) 
     48   INTEGER, PUBLIC, PARAMETER ::   jptra_evd  = 12     !: EVD term (convection) 
     49   INTEGER, PUBLIC, PARAMETER ::   jptra_bbc  = 13     !: Bottom Boundary Condition (geoth. heating)  
     50   INTEGER, PUBLIC, PARAMETER ::   jptra_bbl  = 14     !: Bottom Boundary Layer (diffusive and/or advective) 
     51   INTEGER, PUBLIC, PARAMETER ::   jptra_npc  = 15     !: non-penetrative convection treatment 
     52   INTEGER, PUBLIC, PARAMETER ::   jptra_dmp  = 16     !: internal restoring (damping) 
     53   INTEGER, PUBLIC, PARAMETER ::   jptra_qsr  = 17     !: penetrative solar radiation 
     54   INTEGER, PUBLIC, PARAMETER ::   jptra_nsr  = 18     !: non solar radiation / C/D on salinity  (+runoff if ln_rnf=T) 
     55   INTEGER, PUBLIC, PARAMETER ::   jptra_atf  = 19     !: Asselin time filter 
     56   INTEGER, PUBLIC, PARAMETER ::   jptra_tot  = 20     !: Model total trend 
    5157   ! 
    5258   !                                                  !!!* Passive tracers trends indices (use if "key_top" defined) 
    53    INTEGER, PUBLIC, PARAMETER ::   jptra_sms  = 15     !: sources m. sinks 
    54    INTEGER, PUBLIC, PARAMETER ::   jptra_radn = 16     !: corr. trn<0 in trcrad 
    55    INTEGER, PUBLIC, PARAMETER ::   jptra_radb = 17     !: corr. trb<0 in trcrad (like atf) 
     59   INTEGER, PUBLIC, PARAMETER ::   jptra_sms  = 19     !: sources m. sinks 
     60   INTEGER, PUBLIC, PARAMETER ::   jptra_radn = 20     !: corr. trn<0 in trcrad 
     61   INTEGER, PUBLIC, PARAMETER ::   jptra_radb = 21     !: corr. trb<0 in trcrad (like atf) 
    5662   ! 
    5763   !                                                  !!!* Momentum trends indices 
    58    INTEGER, PUBLIC, PARAMETER ::   jptot_dyn  = 15     !: Total trend nb: change it when adding/removing one indice below 
     64   INTEGER, PUBLIC, PARAMETER ::   jptot_dyn  = 16     !: Total trend nb: change it when adding/removing one indice below 
    5965   !                               ===============     !   
    6066   INTEGER, PUBLIC, PARAMETER ::   jpdyn_hpg  =  1     !: hydrostatic pressure gradient  
     
    7379   INTEGER, PUBLIC, PARAMETER ::   jpdyn_spgflt  = 14  !: filter contribution to surface pressure gradient (spg_flt) 
    7480   INTEGER, PUBLIC, PARAMETER ::   jpdyn_spgexp  = 15  !: explicit contribution to surface pressure gradient (spg_flt) 
     81   INTEGER, PUBLIC, PARAMETER ::   jpdyn_eivke   = 16  !: K.E trend from Gent McWilliams scheme 
    7582   ! 
    7683   !!---------------------------------------------------------------------- 
  • branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD/trdini.F90

    r9816 r9817  
    9191!!gm end 
    9292      ! 
    93       IF( lk_vvl .AND. ( l_trdtra .OR. l_trddyn ) )  CALL ctl_stop( 'trend diagnostics with variable volume not validated' ) 
    9493       
    9594!!gm  : Potential BUG : 3D output only for vector invariant form!  add a ctl_stop or code the flux form case 
  • branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD/trdken.F90

    r9816 r9817  
    2727   USE lib_mpp        ! MPP library 
    2828   USE wrk_nemo       ! Memory allocation 
     29   USE ldfslp         ! Isopycnal slopes 
    2930 
    3031   IMPLICIT NONE 
     
    4243#  include "domzgr_substitute.h90" 
    4344#  include "vectopt_loop_substitute.h90" 
     45#  include "ldfeiv_substitute.h90" 
     46 
    4447   !!---------------------------------------------------------------------- 
    4548   !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     
    117120      ! 
    118121      SELECT CASE( ktrd ) 
    119          CASE( jpdyn_hpg )   ;   CALL iom_put( "ketrd_hpg", zke )    ! hydrostatic pressure gradient 
    120          CASE( jpdyn_spg )   ;   CALL iom_put( "ketrd_spg", zke )    ! surface pressure gradient 
    121          CASE( jpdyn_spgexp );   CALL iom_put( "ketrd_spgexp", zke ) ! surface pressure gradient (explicit) 
    122          CASE( jpdyn_spgflt );   CALL iom_put( "ketrd_spgflt", zke ) ! surface pressure gradient (filter) 
    123          CASE( jpdyn_pvo )   ;   CALL iom_put( "ketrd_pvo", zke )    ! planetary vorticity 
    124          CASE( jpdyn_rvo )   ;   CALL iom_put( "ketrd_rvo", zke )    ! relative  vorticity     (or metric term) 
    125          CASE( jpdyn_keg )   ;   CALL iom_put( "ketrd_keg", zke )    ! Kinetic Energy gradient (or had) 
    126          CASE( jpdyn_zad )   ;   CALL iom_put( "ketrd_zad", zke )    ! vertical   advection 
    127          CASE( jpdyn_ldf )   ;   CALL iom_put( "ketrd_ldf", zke )    ! lateral diffusion 
    128          CASE( jpdyn_zdf )   ;   CALL iom_put( "ketrd_zdf", zke )    ! vertical diffusion  
     122        CASE( jpdyn_hpg )   ;   CALL iom_put( "ketrd_hpg", zke )    ! hydrostatic pressure gradient 
     123        CASE( jpdyn_spg )   ;   CALL iom_put( "ketrd_spg", zke )    ! surface pressure gradient 
     124        CASE( jpdyn_spgexp );   CALL iom_put( "ketrd_spgexp", zke ) ! surface pressure gradient (explicit) 
     125        CASE( jpdyn_spgflt );   CALL iom_put( "ketrd_spgflt", zke ) ! surface pressure gradient (filter) 
     126        CASE( jpdyn_pvo )   ;   CALL iom_put( "ketrd_pvo", zke )    ! planetary vorticity 
     127        CASE( jpdyn_rvo )   ;   CALL iom_put( "ketrd_rvo", zke )    ! relative  vorticity     (or metric term) 
     128        CASE( jpdyn_keg )   ;   CALL iom_put( "ketrd_keg", zke )    ! Kinetic Energy gradient (or had) 
     129        CASE( jpdyn_zad )   ;   CALL iom_put( "ketrd_zad", zke )    ! vertical   advection 
     130        CASE( jpdyn_ldf )   ;   CALL iom_put( "ketrd_ldf", zke )    ! lateral diffusion 
     131        CASE( jpdyn_zdf )   ;   CALL iom_put( "ketrd_zdf", zke )    ! vertical diffusion  
    129132                                 !                                   ! wind stress trends 
    130                                  CALL wrk_alloc( jpi, jpj, z2dx, z2dy, zke2d ) 
    131                            z2dx(:,:) = un(:,:,1) * ( utau_b(:,:) + utau(:,:) ) * e1u(:,:) * e2u(:,:) * umask(:,:,1) 
    132                            z2dy(:,:) = vn(:,:,1) * ( vtau_b(:,:) + vtau(:,:) ) * e1v(:,:) * e2v(:,:) * vmask(:,:,1) 
    133                            zke2d(1,:) = 0._wp   ;   zke2d(:,1) = 0._wp 
    134                            DO jj = 2, jpj 
    135                               DO ji = 2, jpi 
    136                                  zke2d(ji,jj) = 0.5_wp * (   z2dx(ji,jj) + z2dx(ji-1,jj)   & 
    137                                  &                         + z2dy(ji,jj) + z2dy(ji,jj-1)   ) * r1_bt(ji,jj,1) 
    138                               END DO 
    139                            END DO 
    140                                  CALL iom_put( "ketrd_tau", zke2d ) 
    141                                  CALL wrk_dealloc( jpi, jpj     , z2dx, z2dy, zke2d ) 
    142          CASE( jpdyn_bfr )   ;   CALL iom_put( "ketrd_bfr", zke )    ! bottom friction (explicit case)  
     133                                CALL wrk_alloc( jpi, jpj, z2dx, z2dy, zke2d ) 
     134                     z2dx(:,:) = un(:,:,1) * ( utau_b(:,:) + utau(:,:) ) * e1u(:,:) * e2u(:,:) * umask(:,:,1) 
     135                     z2dy(:,:) = vn(:,:,1) * ( vtau_b(:,:) + vtau(:,:) ) * e1v(:,:) * e2v(:,:) * vmask(:,:,1) 
     136                     zke2d(1,:) = 0._wp   ;   zke2d(:,1) = 0._wp 
     137                     DO jj = 2, jpj 
     138                         DO ji = 2, jpi 
     139                           zke2d(ji,jj) = 0.5_wp * (   z2dx(ji,jj) + z2dx(ji-1,jj)   & 
     140                            &                         + z2dy(ji,jj) + z2dy(ji,jj-1)   ) * r1_bt(ji,jj,1) 
     141                         END DO 
     142                     END DO 
     143                                CALL iom_put( "ketrd_tau", zke2d ) 
     144                                CALL wrk_dealloc( jpi, jpj     , z2dx, z2dy, zke2d ) 
     145        CASE( jpdyn_bfr )   ;   CALL iom_put( "ketrd_bfr", zke )    ! bottom friction (explicit case)  
    143146!!gm TO BE DONE properly 
    144147!!gm only valid if ln_bfrimp=F otherwise the bottom stress as to be recomputed at the end of the computation.... 
     
    162165!         ENDIF 
    163166!!gm end 
    164          CASE( jpdyn_atf )   ;   CALL iom_put( "ketrd_atf", zke )    ! asselin filter trends  
     167        CASE( jpdyn_atf )   ;   CALL iom_put( "ketrd_atf", zke )    ! asselin filter trends  
    165168!! a faire !!!!  idee changer dynnxt pour avoir un appel a jpdyn_bfr avant le swap !!! 
    166169!! reflechir a une possible sauvegarde du "vrai" un,vn pour le calcul de atf.... 
     
    184187!                              CALL iom_put( "ketrd_bfri", zke2d ) 
    185188!         ENDIF 
    186          CASE( jpdyn_ken )   ;   ! kinetic energy 
    187                            ! called in dynnxt.F90 before asselin time filter 
    188                            ! with putrd=ua and pvtrd=va 
    189                            zke(:,:,:) = 0.5_wp * zke(:,:,:) 
    190                            CALL iom_put( "KE", zke ) 
    191                            ! 
    192                            CALL ken_p2k( kt , zke ) 
    193                            CALL iom_put( "ketrd_convP2K", zke )     ! conversion -rau*g*w 
     189        CASE( jpdyn_ken )   ;   ! kinetic energy 
     190                    ! called in dynnxt.F90 before asselin time filter 
     191                    ! with putrd=ua and pvtrd=va 
     192                    zke(:,:,:) = 0.5_wp * zke(:,:,:) 
     193                    CALL iom_put( "KE", zke ) 
     194                    ! 
     195                    CALL ken_p2k( kt , zke ) 
     196                      CALL iom_put( "ketrd_convP2K", zke )     ! conversion -rau*g*w 
     197        CASE( jpdyn_eivke ) 
     198            ! CMIP6 diagnostic tknebto = tendency of KE from 
     199            ! parameterized mesoscale eddy advection 
     200            ! = vertical_integral( k (N S)^2 ) rho dz 
     201            ! rho = reference density 
     202            ! S = isoneutral slope. 
     203            ! Most terms are on W grid so work on this grid 
     204            CALL wrk_alloc( jpi, jpj, zke2d ) 
     205            zke2d(:,:) = 0._wp 
     206            DO jk = 1,jpk 
     207               DO ji = 1,jpi 
     208                  DO jj = 1,jpj 
     209                     zke2d(ji,jj) = zke2d(ji,jj) +  rau0 * fsaeiw(ji, jj, jk)               & 
     210                          &                      * ( wslpi(ji, jj, jk) * wslpi(ji,jj,jk)    & 
     211                          &                      +   wslpj(ji, jj, jk) * wslpj(ji,jj,jk) )  & 
     212                          &                      *   rn2(ji,jj,jk) * fse3w(ji, jj, jk) 
     213                  ENDDO 
     214               ENDDO 
     215            ENDDO 
     216            CALL iom_put("ketrd_eiv", zke2d) 
     217            CALL wrk_dealloc( jpi, jpj, zke2d ) 
    194218         ! 
    195219      END SELECT 
  • branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl.F90

    r9816 r9817  
    165165 
    166166 
    167       SELECT CASE( ktrd ) 
    168       CASE( jptra_npc  )               ! non-penetrative convection: regrouped with zdf 
     167      SELECT CASE( ktrd ) 
     168      CASE( jptra_npc  )               ! non-penetrative convection: regrouped with zdf 
    169169!!gm : to be completed !  
    170 !        IF( .... 
     170!         IF( .... 
    171171!!gm end 
    172       CASE( jptra_zdfp )               ! iso-neutral diffusion: "pure" vertical diffusion 
    173          !                                   ! regroup iso-neutral diffusion in one term 
     172      CASE( jptra_zdfp )               ! iso-neutral diffusion: "pure" vertical diffusion 
     173         !                                   ! regroup iso-neutral diffusion in one term 
    174174         tmltrd(:,:,jpmxl_ldf) = tmltrd(:,:,jpmxl_ldf) + ( tmltrd(:,:,jpmxl_zdf) - tmltrd(:,:,jpmxl_zdfp) ) 
    175175         smltrd(:,:,jpmxl_ldf) = smltrd(:,:,jpmxl_ldf) + ( smltrd(:,:,jpmxl_zdf) - smltrd(:,:,jpmxl_zdfp) ) 
     
    811811 
    812812 
    813       nkstp     = nit000 - 1              ! current time step indicator initialization 
     813      nkstp     = nit000 - 1              ! current time step indicator initialization 
    814814 
    815815 
     
    851851      IF( nn_ctls == 1 ) THEN 
    852852         CALL ctl_opn( inum, 'ctlsurf_idx', 'OLD', 'UNFORMATTED', 'SEQUENTIAL', -1, numout, lwp ) 
    853          READ ( inum ) nbol 
     853         READ ( inum, * ) nbol 
    854854         CLOSE( inum ) 
    855855      END IF 
  • branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD/trdmxl_oce.F90

    r9816 r9817  
    1515 
    1616   !                                                !* mixed layer trend indices 
    17    INTEGER, PUBLIC, PARAMETER ::   jpltrd = 11      !: number of mixed-layer trends arrays 
     17   INTEGER, PUBLIC, PARAMETER ::   jpltrd = 12      !: number of mixed-layer trends arrays 
    1818   INTEGER, PUBLIC            ::   jpktrd           !: max level for mixed-layer trends diag. 
    1919   ! 
     
    2828   INTEGER, PUBLIC, PARAMETER ::   jpmxl_for =  9   !: forcing  
    2929   INTEGER, PUBLIC, PARAMETER ::   jpmxl_dmp = 10   !: internal restoring trend 
    30    INTEGER, PUBLIC, PARAMETER ::   jpmxl_zdfp = 11   !: asselin trend (**MUST BE THE LAST ONE**) 
    31    INTEGER, PUBLIC, PARAMETER ::   jpmxl_atf  = 12   !: asselin trend (**MUST BE THE LAST ONE**) 
     30   INTEGER, PUBLIC, PARAMETER ::   jpmxl_zdfp = 11  !: iso-neutral diffusion:"pure" vertical diffusion 
     31   INTEGER, PUBLIC, PARAMETER ::   jpmxl_atf  = 12  !: asselin trend (**MUST BE THE LAST ONE**) 
    3232   !                                                            !!* Namelist namtrd_mxl:  trend diagnostics in the mixed layer * 
    3333   INTEGER           , PUBLIC ::   nn_ctls  = 0                  !: control surface type for trends vertical integration 
  • branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD/trdpen.F90

    r9816 r9817  
    9999                                   CALL wrk_alloc( jpi, jpj, z2d ) 
    100100                                   z2d(:,:) = wn(:,:,1) * ( & 
    101                                       &   - ( rab_n(:,:,1,jp_tem) + rab_pe(:,:,1,jp_tem) ) * tsn(:,:,1,jp_tem)    & 
    102                                       &   + ( rab_n(:,:,1,jp_sal) + rab_pe(:,:,1,jp_sal) ) * tsn(:,:,1,jp_sal)    & 
    103                                       &                  ) / fse3t(:,:,1) 
     101                                       &   - ( rab_n(:,:,1,jp_tem) + rab_pe(:,:,1,jp_tem) ) * tsn(:,:,1,jp_tem)    & 
     102                                       &   + ( rab_n(:,:,1,jp_sal) + rab_pe(:,:,1,jp_sal) ) * tsn(:,:,1,jp_sal)    & 
     103                                       &             ) / fse3t(:,:,1) 
    104104                                   CALL iom_put( "petrd_sad" , z2d ) 
    105105                                   CALL wrk_dealloc( jpi, jpj, z2d ) 
     
    150150      rab_pe(:,:,:,:) = 0._wp 
    151151      ! 
    152       IF ( lk_vvl               )   CALL ctl_stop('trd_pen_init : PE trends not coded for variable volume') 
     152!      IF ( lk_vvl               )   CALL ctl_stop('trd_pen_init : PE trends not coded for variable volume') 
    153153      ! 
    154154      nkstp     = nit000 - 1 
  • branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD/trdtra.F90

    r9816 r9817  
    3838   REAL(wp) ::   r2dt   ! time-step, = 2 rdttra except at nit000 (=rdttra) if neuler=0 
    3939 
    40    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   trdtx, trdty, trdt   ! use to store the temperature trends 
     40   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   trdtx, trdty, trdt  ! use to store the temperature trends 
     41   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   avt_evd  ! store avt_evd to calculate EVD trend 
    4142 
    4243   !! * Substitutions 
     
    5556      !!                  ***  FUNCTION trd_tra_alloc  *** 
    5657      !!--------------------------------------------------------------------- 
    57       ALLOCATE( trdtx(jpi,jpj,jpk) , trdty(jpi,jpj,jpk) , trdt(jpi,jpj,jpk) , STAT= trd_tra_alloc ) 
     58      ALLOCATE( trdtx(jpi,jpj,jpk) , trdty(jpi,jpj,jpk) , trdt(jpi,jpj,jpk) , avt_evd(jpi,jpj,jpk), STAT= trd_tra_alloc ) 
    5859      ! 
    5960      IF( lk_mpp             )   CALL mpp_sum ( trd_tra_alloc ) 
     
    104105                                 ztrds(:,:,:) = 0._wp 
    105106                                 CALL trd_tra_mng( trdt, ztrds, ktrd, kt ) 
     107         CASE( jptra_evd )   ;   avt_evd(:,:,:) = ptrd(:,:,:) * tmask(:,:,:) 
    106108         CASE DEFAULT                 ! other trends: masked trends 
    107109            trdt(:,:,:) = ptrd(:,:,:) * tmask(:,:,:)              ! mask & store 
     
    128130            zwt(:,:,jpk) = 0._wp   ;   zws(:,:,jpk) = 0._wp 
    129131            DO jk = 2, jpk 
    130                zwt(:,:,jk) =   avt(:,:,jk) * ( tsa(:,:,jk-1,jp_tem) - tsa(:,:,jk,jp_tem) ) / fse3w(:,:,jk) * tmask(:,:,jk) 
     132               zwt(:,:,jk) = avt(:,:,jk) * ( tsa(:,:,jk-1,jp_tem) - tsa(:,:,jk,jp_tem) ) / fse3w(:,:,jk) * tmask(:,:,jk) 
    131133               zws(:,:,jk) = fsavs(:,:,jk) * ( tsa(:,:,jk-1,jp_sal) - tsa(:,:,jk,jp_sal) ) / fse3w(:,:,jk) * tmask(:,:,jk) 
    132134            END DO 
     
    138140            END DO 
    139141            CALL trd_tra_mng( ztrdt, ztrds, jptra_zdfp, kt )   
     142            ! 
     143            !                         ! Also calculate EVD trend at this point.  
     144            zwt(:,:,:) = 0._wp   ;   zws(:,:,:) = 0._wp            ! vertical diffusive fluxes 
     145            DO jk = 2, jpk 
     146               zwt(:,:,jk) = avt_evd(:,:,jk) * ( tsa(:,:,jk-1,jp_tem) - tsa(:,:,jk,jp_tem) ) / fse3w(:,:,jk) * tmask(:,:,jk) 
     147               zws(:,:,jk) = avt_evd(:,:,jk) * ( tsa(:,:,jk-1,jp_sal) - tsa(:,:,jk,jp_sal) ) / fse3w(:,:,jk) * tmask(:,:,jk) 
     148            END DO 
     149            ! 
     150            ztrdt(:,:,jpk) = 0._wp   ;   ztrds(:,:,jpk) = 0._wp 
     151            DO jk = 1, jpkm1 
     152               ztrdt(:,:,jk) = ( zwt(:,:,jk) - zwt(:,:,jk+1) ) / fse3t(:,:,jk) 
     153               ztrds(:,:,jk) = ( zws(:,:,jk) - zws(:,:,jk+1) ) / fse3t(:,:,jk)  
     154            END DO 
     155            CALL trd_tra_mng( ztrdt, ztrds, jptra_evd, kt )   
    140156            ! 
    141157            CALL wrk_dealloc( jpi, jpj, jpk, zwt, zws, ztrdt ) 
     
    285301      !! ** Purpose :   output 3D tracer trends using IOM 
    286302      !!---------------------------------------------------------------------- 
    287       REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdx   ! Temperature or U trend  
    288       REAL(wp), DIMENSION(:,:,:), INTENT(inout) ::   ptrdy   ! Salinity    or V trend 
    289       INTEGER                   , INTENT(in   ) ::   ktrd    ! tracer trend index 
    290       INTEGER                   , INTENT(in   ) ::   kt      ! time step 
    291       !! 
    292       INTEGER ::   ji, jj, jk   ! dummy loop indices 
    293       INTEGER ::   ikbu, ikbv   ! local integers 
    294       REAL(wp), POINTER, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace  
    295       !!---------------------------------------------------------------------- 
    296       ! 
    297 !!gm Rq: mask the trends already masked in trd_tra, but lbc_lnk should probably be added 
    298       ! 
    299       SELECT CASE( ktrd ) 
    300       CASE( jptra_xad  )   ;   CALL iom_put( "ttrd_xad" , ptrdx )        ! x- horizontal advection 
    301                                CALL iom_put( "strd_xad" , ptrdy ) 
    302       CASE( jptra_yad  )   ;   CALL iom_put( "ttrd_yad" , ptrdx )        ! y- horizontal advection 
    303                                CALL iom_put( "strd_yad" , ptrdy ) 
    304       CASE( jptra_zad  )   ;   CALL iom_put( "ttrd_zad" , ptrdx )        ! z- vertical   advection 
    305                                CALL iom_put( "strd_zad" , ptrdy ) 
    306                                IF( .NOT. lk_vvl ) THEN                   ! cst volume : adv flux through z=0 surface 
    307                                   CALL wrk_alloc( jpi, jpj, z2dx, z2dy ) 
    308                                   z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / fse3t(:,:,1) 
    309                                   z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / fse3t(:,:,1) 
    310                                   CALL iom_put( "ttrd_sad", z2dx ) 
    311                                   CALL iom_put( "strd_sad", z2dy ) 
    312                                   CALL wrk_dealloc( jpi, jpj, z2dx, z2dy ) 
    313                                ENDIF 
    314       CASE( jptra_ldf  )   ;   CALL iom_put( "ttrd_ldf" , ptrdx )        ! lateral diffusion 
    315                                CALL iom_put( "strd_ldf" , ptrdy ) 
    316       CASE( jptra_zdf  )   ;   CALL iom_put( "ttrd_zdf" , ptrdx )        ! vertical diffusion (including Kz contribution) 
    317                                CALL iom_put( "strd_zdf" , ptrdy ) 
    318       CASE( jptra_zdfp )   ;   CALL iom_put( "ttrd_zdfp", ptrdx )        ! PURE vertical diffusion (no isoneutral contribution) 
    319                                CALL iom_put( "strd_zdfp", ptrdy ) 
    320       CASE( jptra_dmp  )   ;   CALL iom_put( "ttrd_dmp" , ptrdx )        ! internal restoring (damping) 
    321                                CALL iom_put( "strd_dmp" , ptrdy ) 
    322       CASE( jptra_bbl  )   ;   CALL iom_put( "ttrd_bbl" , ptrdx )        ! bottom boundary layer 
    323                                CALL iom_put( "strd_bbl" , ptrdy ) 
    324       CASE( jptra_npc  )   ;   CALL iom_put( "ttrd_npc" , ptrdx )        ! static instability mixing 
    325                                CALL iom_put( "strd_npc" , ptrdy ) 
    326       CASE( jptra_nsr  )   ;   CALL iom_put( "ttrd_qns" , ptrdx )        ! surface forcing + runoff (ln_rnf=T) 
    327                                CALL iom_put( "strd_cdt" , ptrdy ) 
    328       CASE( jptra_qsr  )   ;   CALL iom_put( "ttrd_qsr" , ptrdx )        ! penetrative solar radiat. (only on temperature) 
    329       CASE( jptra_bbc  )   ;   CALL iom_put( "ttrd_bbc" , ptrdx )        ! geothermal heating   (only on temperature) 
    330       CASE( jptra_atf  )   ;   CALL iom_put( "ttrd_atf" , ptrdx )        ! asselin time Filter 
    331                                CALL iom_put( "strd_atf" , ptrdy ) 
    332       END SELECT 
    333       ! 
     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     ! 
    334369   END SUBROUTINE trd_tra_iom 
    335370 
  • branches/UKMO/dev_r5518_nemo2cice_prints/NEMOGCM/NEMO/OPA_SRC/TRD/trdtrc.F90

    r9816 r9817  
     1#if ! defined key_top 
    12MODULE trdtrc 
    23   !!====================================================================== 
     
    2223   !!====================================================================== 
    2324END MODULE trdtrc 
     25#endif 
Note: See TracChangeset for help on using the changeset viewer.