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/trdtra.F90 – 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.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • 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 
Note: See TracChangeset for help on using the changeset viewer.