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 12622 for NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/DIA/diawri.F90 – NEMO

Ignore:
Timestamp:
2020-03-27T20:55:44+01:00 (4 years ago)
Author:
techene
Message:

all: add e3 substitute (sometimes it requires to add ze3t/u/v/w) and limit precompiled files lines to about 130 character

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12377_KERNEL-06_techene_e3/src/OCE/DIA/diawri.F90

    r12377 r12622  
    8585   !! * Substitutions 
    8686#  include "do_loop_substitute.h90" 
     87#  include "domzgr_substitute.h90" 
    8788   !!---------------------------------------------------------------------- 
    8889   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    120121      REAL(wp)::   zztmp2, zztmpy   !   -      - 
    121122      REAL(wp), DIMENSION(jpi,jpj)     ::   z2d   ! 2D workspace 
    122       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   z3d   ! 3D workspace 
     123      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   z3d, ze3t, ze3u, ze3v, ze3w   ! 3D workspace 
    123124      !!---------------------------------------------------------------------- 
    124125      !  
     
    136137      CALL iom_put("e3v_0", e3v_0(:,:,:) ) 
    137138      ! 
    138       CALL iom_put( "e3t" , e3t(:,:,:,Kmm) ) 
    139       CALL iom_put( "e3u" , e3u(:,:,:,Kmm) ) 
    140       CALL iom_put( "e3v" , e3v(:,:,:,Kmm) ) 
    141       CALL iom_put( "e3w" , e3w(:,:,:,Kmm) ) 
     139      DO jk = 1, jpk 
     140         ze3t(:,:,jk) =  e3t(:,:,jk,Kmm) 
     141         ze3u(:,:,jk) =  e3u(:,:,jk,Kmm) 
     142         ze3v(:,:,jk) =  e3v(:,:,jk,Kmm) 
     143         ze3w(:,:,jk) =  e3w(:,:,jk,Kmm) 
     144      END DO  
     145      ! 
     146      CALL iom_put( "e3t" , ze3t(:,:,:) ) 
     147      CALL iom_put( "e3u" , ze3u(:,:,:) ) 
     148      CALL iom_put( "e3v" , ze3v(:,:,:) ) 
     149      CALL iom_put( "e3w" , ze3w(:,:,:) ) 
    142150      IF( iom_use("e3tdef") )   & 
    143          CALL iom_put( "e3tdef"  , ( ( e3t(:,:,:,Kmm) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 ) 
     151         CALL iom_put( "e3tdef"  , ( ( ze3t(:,:,:) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 ) !!st r3t 
    144152 
    145153      IF( ll_wd ) THEN 
     
    410418      ! 
    411419      REAL(wp), DIMENSION(jpi,jpj)   :: zw2d       ! 2D workspace 
    412       REAL(wp), DIMENSION(jpi,jpj,jpk) :: zw3d       ! 3D workspace 
     420      REAL(wp), DIMENSION(jpi,jpj,jpk) :: zw3d, ze3t       ! 3D workspace 
    413421      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zw3d_abl   ! ABL 3D workspace 
    414422      !!---------------------------------------------------------------------- 
     
    450458      it = kt 
    451459      itmod = kt - nit000 + 1 
     460 
     461      ! store e3t for subsitute 
     462      DO jk = 1, jpk 
     463         ze3t(:,:,jk) =  e3t(:,:,jk,Kmm) 
     464      END DO 
    452465 
    453466 
     
    564577         DEALLOCATE(zw3d_abl) 
    565578         ENDIF 
     579         ! 
    566580 
    567581         ! Declare all the output fields as NETCDF variables 
     
    573587            &          jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout ) 
    574588         IF(  .NOT.ln_linssh  ) THEN 
    575             CALL histdef( nid_T, "vovvle3t", "Level thickness"                    , "m"      ,&  ! e3t(:,:,:,Kmm) 
     589            CALL histdef( nid_T, "vovvle3t", "Level thickness"                    , "m"      ,&  ! e3t n 
    576590            &             jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout ) 
    577             CALL histdef( nid_T, "vovvldep", "T point depth"                      , "m"      ,&  ! e3t(:,:,:,Kmm) 
     591            CALL histdef( nid_T, "vovvldep", "T point depth"                      , "m"      ,&  ! e3t n 
    578592            &             jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout ) 
    579             CALL histdef( nid_T, "vovvldef", "Squared level deformation"          , "%^2"    ,&  ! e3t(:,:,:,Kmm) 
     593            CALL histdef( nid_T, "vovvldef", "Squared level deformation"          , "%^2"    ,&  ! e3t n 
    580594            &             jpi, jpj, nh_T, ipk, 1, ipk, nz_T, 32, clop, zsto, zout ) 
    581595         ENDIF 
     
    761775 
    762776      IF( .NOT.ln_linssh ) THEN 
    763          CALL histwrite( nid_T, "votemper", it, ts(:,:,:,jp_tem,Kmm) * e3t(:,:,:,Kmm) , ndim_T , ndex_T  )   ! heat content 
    764          CALL histwrite( nid_T, "vosaline", it, ts(:,:,:,jp_sal,Kmm) * e3t(:,:,:,Kmm) , ndim_T , ndex_T  )   ! salt content 
     777         CALL histwrite( nid_T, "votemper", it, ts(:,:,:,jp_tem,Kmm) * ze3t(:,:,:) , ndim_T , ndex_T  )   ! heat content 
     778         CALL histwrite( nid_T, "vosaline", it, ts(:,:,:,jp_sal,Kmm) * ze3t(:,:,:) , ndim_T , ndex_T  )   ! salt content 
    765779         CALL histwrite( nid_T, "sosstsst", it, ts(:,:,1,jp_tem,Kmm) * e3t(:,:,1,Kmm) , ndim_hT, ndex_hT )   ! sea surface heat content 
    766780         CALL histwrite( nid_T, "sosaline", it, ts(:,:,1,jp_sal,Kmm) * e3t(:,:,1,Kmm) , ndim_hT, ndex_hT )   ! sea surface salinity content 
     
    772786      ENDIF 
    773787      IF( .NOT.ln_linssh ) THEN 
    774          zw3d(:,:,:) = ( ( e3t(:,:,:,Kmm) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 
    775          CALL histwrite( nid_T, "vovvle3t", it, e3t (:,:,:,Kmm) , ndim_T , ndex_T  )   ! level thickness 
     788         zw3d(:,:,:) = ( ( ze3t(:,:,:) - e3t_0(:,:,:) ) / e3t_0(:,:,:) * 100 * tmask(:,:,:) ) ** 2 
     789         CALL histwrite( nid_T, "vovvle3t", it, ze3t (:,:,:)    , ndim_T , ndex_T  )   ! level thickness 
    776790         CALL histwrite( nid_T, "vovvldep", it, gdept(:,:,:,Kmm) , ndim_T , ndex_T  )   ! t-point depth 
    777791         CALL histwrite( nid_T, "vovvldef", it, zw3d             , ndim_T , ndex_T  )   ! level thickness deformation 
     
    913927      !! 
    914928      INTEGER :: inum, jk 
     929      REAL(wp), DIMENSION(jpi,jpj,jpk) :: ze3t       ! 3D workspace 
    915930      !!---------------------------------------------------------------------- 
    916931      !  
     
    919934      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~   and forcing fields file created ' 
    920935      IF(lwp) WRITE(numout,*) '                and named :', cdfile_name, '...nc' 
     936 
     937      DO jk = 1, jpk 
     938         ze3t(:,:,jk) =  e3t(:,:,jk,Kmm) 
     939      END DO 
    921940 
    922941#if defined key_si3 
     
    975994      IF(  .NOT.ln_linssh  ) THEN              
    976995         CALL iom_rstput( 0, 0, inum, 'vovvldep', gdept(:,:,:,Kmm)        )    !  T-cell depth  
    977          CALL iom_rstput( 0, 0, inum, 'vovvle3t', e3t(:,:,:,Kmm)          )    !  T-cell thickness   
     996         CALL iom_rstput( 0, 0, inum, 'vovvle3t', ze3t(:,:,:)          )    !  T-cell thickness   
    978997      END IF 
    979998      IF( ln_wave .AND. ln_sdw ) THEN 
Note: See TracChangeset for help on using the changeset viewer.