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 8850 for branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/OPA_SRC/TRD – NEMO

Ignore:
Timestamp:
2017-11-30T09:30:44+01:00 (7 years ago)
Author:
gm
Message:

#1911 (ENHANCE-09): PART I.3 - phasing with trunk: tracer trends output (see #1877 trunk change from 86666 to 8698)

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/OPA_SRC/TRD/trdtra.F90

    r8215 r8850  
    3131   USE iom            ! I/O manager library 
    3232   USE lib_mpp        ! MPP library 
    33    USE wrk_nemo       ! Memory allocation 
    3433 
    3534   IMPLICIT NONE 
     
    8281      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(in), OPTIONAL ::   ptra    ! now tracer variable 
    8382      ! 
    84       INTEGER  ::   jk   ! loop indices 
    85       REAL(wp), POINTER, DIMENSION(:,:,:)  ::   zwt, zws, ztrdt, ztrds   ! 3D workspace 
    86       !!---------------------------------------------------------------------- 
    87       ! 
    88       CALL wrk_alloc( jpi, jpj, jpk, ztrds ) 
     83      INTEGER ::   jk   ! loop indices 
     84      REAL(wp),        DIMENSION(jpi,jpj,jpk) ::   ztrds             ! 3D workspace 
     85      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   zwt, zws, ztrdt   ! 3D workspace 
     86      !!---------------------------------------------------------------------- 
    8987      !       
    9088      IF( .NOT. ALLOCATED( trdtx ) ) THEN      ! allocate trdtra arrays 
     
    103101                                 ztrds(:,:,:) = 0._wp 
    104102                                 CALL trd_tra_mng( trdt, ztrds, ktrd, kt ) 
     103 !!gm Gurvan, verify the jptra_evd trend please ! 
     104         CASE( jptra_evd )   ;   avt_evd(:,:,:) = ptrd(:,:,:) * tmask(:,:,:) 
    105105         CASE DEFAULT                 ! other trends: masked trends 
    106106            trdt(:,:,:) = ptrd(:,:,:) * tmask(:,:,:)              ! mask & store 
     
    122122         CASE( jptra_zdfp )           ! diagnose the "PURE" Kz trend (here: just before the swap) 
    123123            !                         ! iso-neutral diffusion case otherwise jptra_zdf is "PURE" 
    124             CALL wrk_alloc( jpi, jpj, jpk, zwt, zws, ztrdt ) 
     124            ALLOCATE( zwt(jpi,jpj,jpk), zws(jpi,jpj,jpk), ztrdt(jpi,jpj,jpk) ) 
    125125            ! 
    126126            zwt(:,:, 1 ) = 0._wp   ;   zws(:,:, 1 ) = 0._wp            ! vertical diffusive fluxes 
     
    152152            CALL trd_tra_mng( ztrdt, ztrds, jptra_evd, kt )   
    153153            ! 
    154             CALL wrk_dealloc( jpi, jpj, jpk, zwt, zws, ztrdt ) 
     154            DEALLOCATE( zwt, zws, ztrdt ) 
    155155            ! 
    156156         CASE DEFAULT                 ! other trends: mask and send T & S trends to trd_tra_mng 
     
    174174         ! 
    175175      ENDIF 
    176       ! 
    177       CALL wrk_dealloc( jpi, jpj, jpk, ztrds ) 
    178176      ! 
    179177   END SUBROUTINE trd_tra 
     
    305303      INTEGER ::   ji, jj, jk   ! dummy loop indices 
    306304      INTEGER ::   ikbu, ikbv   ! local integers 
    307       REAL(wp), POINTER, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace  
     305      REAL(wp), ALLOCATABLE, DIMENSION(:,:)   ::   z2dx, z2dy   ! 2D workspace  
    308306      !!---------------------------------------------------------------------- 
    309307      ! 
    310308!!gm Rq: mask the trends already masked in trd_tra, but lbc_lnk should probably be added 
    311309      ! 
     310      ! 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 
    312311      SELECT CASE( ktrd ) 
    313       CASE( jptra_xad  )   ;   CALL iom_put( "ttrd_xad" , ptrdx )        ! x- horizontal advection 
    314                                CALL iom_put( "strd_xad" , ptrdy ) 
    315       CASE( jptra_yad  )   ;   CALL iom_put( "ttrd_yad" , ptrdx )        ! y- horizontal advection 
    316                                CALL iom_put( "strd_yad" , ptrdy ) 
    317       CASE( jptra_zad  )   ;   CALL iom_put( "ttrd_zad" , ptrdx )        ! z- vertical   advection 
    318                                CALL iom_put( "strd_zad" , ptrdy ) 
    319                                IF( ln_linssh ) THEN                   ! cst volume : adv flux through z=0 surface 
    320                                   CALL wrk_alloc( jpi, jpj, z2dx, z2dy ) 
    321                                   z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / e3t_n(:,:,1) 
    322                                   z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / e3t_n(:,:,1) 
    323                                   CALL iom_put( "ttrd_sad", z2dx ) 
    324                                   CALL iom_put( "strd_sad", z2dy ) 
    325                                   CALL wrk_dealloc( jpi, jpj, z2dx, z2dy ) 
    326                                ENDIF 
    327       CASE( jptra_totad  ) ;   CALL iom_put( "ttrd_totad" , ptrdx )      ! total   advection 
    328                                CALL iom_put( "strd_totad" , ptrdy ) 
    329       CASE( jptra_ldf  )   ;   CALL iom_put( "ttrd_ldf" , ptrdx )        ! lateral diffusion 
    330                                CALL iom_put( "strd_ldf" , ptrdy ) 
    331       CASE( jptra_zdf  )   ;   CALL iom_put( "ttrd_zdf" , ptrdx )        ! vertical diffusion (including Kz contribution) 
    332                                CALL iom_put( "strd_zdf" , ptrdy ) 
    333       CASE( jptra_zdfp )   ;   CALL iom_put( "ttrd_zdfp", ptrdx )        ! PURE vertical diffusion (no isoneutral contribution) 
    334                                CALL iom_put( "strd_zdfp", ptrdy ) 
    335       CASE( jptra_evd )    ;   CALL iom_put( "ttrd_evd", ptrdx )         ! EVD trend (convection) 
    336                                CALL iom_put( "strd_evd", ptrdy ) 
    337       CASE( jptra_dmp  )   ;   CALL iom_put( "ttrd_dmp" , ptrdx )        ! internal restoring (damping) 
    338                                CALL iom_put( "strd_dmp" , ptrdy ) 
    339       CASE( jptra_bbl  )   ;   CALL iom_put( "ttrd_bbl" , ptrdx )        ! bottom boundary layer 
    340                                CALL iom_put( "strd_bbl" , ptrdy ) 
    341       CASE( jptra_npc  )   ;   CALL iom_put( "ttrd_npc" , ptrdx )        ! static instability mixing 
    342                                CALL iom_put( "strd_npc" , ptrdy ) 
    343       CASE( jptra_nsr  )   ;   CALL iom_put( "ttrd_qns" , ptrdx(:,:,1) )        ! surface forcing + runoff (ln_rnf=T) 
    344                                CALL iom_put( "strd_cdt" , ptrdy(:,:,1) )        ! output as 2D surface fields 
    345       CASE( jptra_qsr  )   ;   CALL iom_put( "ttrd_qsr" , ptrdx )        ! penetrative solar radiat. (only on temperature) 
    346       CASE( jptra_bbc  )   ;   CALL iom_put( "ttrd_bbc" , ptrdx )        ! geothermal heating   (only on temperature) 
    347       CASE( jptra_atf  )   ;   CALL iom_put( "ttrd_atf" , ptrdx )        ! asselin time Filter 
    348                                CALL iom_put( "strd_atf" , ptrdy ) 
    349       CASE( jptra_tot  )   ;   CALL iom_put( "ttrd_tot" , ptrdx )        ! model total trend 
     312      ! This total trend is done every time step 
     313      CASE( jptra_tot  )   ;   CALL iom_put( "ttrd_tot" , ptrdx )           ! model total trend 
    350314                               CALL iom_put( "strd_tot" , ptrdy ) 
    351315      END SELECT 
    352316      ! 
     317      ! These trends are done every second time step. When 1ts output is selected must go different (2ts) file from standard T-file 
     318      IF( MOD( kt, 2 ) == 0 ) THEN 
     319         SELECT CASE( ktrd ) 
     320         CASE( jptra_xad  )   ;   CALL iom_put( "ttrd_xad"  , ptrdx )         ! x- horizontal advection 
     321                                  CALL iom_put( "strd_xad"  , ptrdy ) 
     322         CASE( jptra_yad  )   ;   CALL iom_put( "ttrd_yad"  , ptrdx )         ! y- horizontal advection 
     323                                  CALL iom_put( "strd_yad"  , ptrdy ) 
     324         CASE( jptra_zad  )   ;   CALL iom_put( "ttrd_zad"  , ptrdx )         ! z- vertical   advection 
     325                                  CALL iom_put( "strd_zad"  , ptrdy ) 
     326                                  IF( ln_linssh ) THEN                   ! cst volume : adv flux through z=0 surface 
     327                                     ALLOCATE( z2dx(jpi,jpj) , z2dy(jpi,jpj) ) 
     328                                     z2dx(:,:) = wn(:,:,1) * tsn(:,:,1,jp_tem) / e3t_n(:,:,1) 
     329                                     z2dy(:,:) = wn(:,:,1) * tsn(:,:,1,jp_sal) / e3t_n(:,:,1) 
     330                                     CALL iom_put( "ttrd_sad", z2dx ) 
     331                                     CALL iom_put( "strd_sad", z2dy ) 
     332                                     DEALLOCATE( z2dx, z2dy ) 
     333                                  ENDIF 
     334         CASE( jptra_totad  ) ;   CALL iom_put( "ttrd_totad", ptrdx )         ! total   advection 
     335                                  CALL iom_put( "strd_totad", ptrdy ) 
     336         CASE( jptra_ldf  )   ;   CALL iom_put( "ttrd_ldf"  , ptrdx )         ! lateral diffusion 
     337                                  CALL iom_put( "strd_ldf"  , ptrdy ) 
     338         CASE( jptra_zdf  )   ;   CALL iom_put( "ttrd_zdf"  , ptrdx )         ! vertical diffusion (including Kz contribution) 
     339                                  CALL iom_put( "strd_zdf"  , ptrdy ) 
     340         CASE( jptra_zdfp )   ;   CALL iom_put( "ttrd_zdfp" , ptrdx )         ! PURE vertical diffusion (no isoneutral contribution) 
     341                                  CALL iom_put( "strd_zdfp" , ptrdy ) 
     342         CASE( jptra_evd )    ;   CALL iom_put( "ttrd_evd"  , ptrdx )         ! EVD trend (convection) 
     343                                  CALL iom_put( "strd_evd"  , ptrdy ) 
     344         CASE( jptra_dmp  )   ;   CALL iom_put( "ttrd_dmp"  , ptrdx )         ! internal restoring (damping) 
     345                                  CALL iom_put( "strd_dmp"  , ptrdy ) 
     346         CASE( jptra_bbl  )   ;   CALL iom_put( "ttrd_bbl"  , ptrdx )         ! bottom boundary layer 
     347                                  CALL iom_put( "strd_bbl"  , ptrdy ) 
     348         CASE( jptra_npc  )   ;   CALL iom_put( "ttrd_npc"  , ptrdx )         ! static instability mixing 
     349                                  CALL iom_put( "strd_npc"  , ptrdy ) 
     350         CASE( jptra_bbc  )   ;   CALL iom_put( "ttrd_bbc"  , ptrdx )         ! geothermal heating   (only on temperature) 
     351         CASE( jptra_nsr  )   ;   CALL iom_put( "ttrd_qns"  , ptrdx(:,:,1) )  ! surface forcing + runoff (ln_rnf=T) 
     352                                  CALL iom_put( "strd_cdt"  , ptrdy(:,:,1) )        ! output as 2D surface fields 
     353         CASE( jptra_qsr  )   ;   CALL iom_put( "ttrd_qsr"  , ptrdx )         ! penetrative solar radiat. (only on temperature) 
     354         END SELECT 
     355         ! the Asselin filter trend  is also every other time step but needs to be lagged one time step 
     356         ! Even when 1ts output is selected can go to the same (2ts) file as the trends plotted every even time step. 
     357      ELSEIF( MOD( kt, 2 ) == 1 ) THEN 
     358         SELECT CASE( ktrd ) 
     359         CASE( jptra_atf  )   ;   CALL iom_put( "ttrd_atf" , ptrdx )        ! asselin time Filter 
     360                                  CALL iom_put( "strd_atf" , ptrdy ) 
     361         END SELECT 
     362      ENDIF 
     363      ! 
    353364   END SUBROUTINE trd_tra_iom 
    354365 
Note: See TracChangeset for help on using the changeset viewer.