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 9939 for NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA – NEMO

Ignore:
Timestamp:
2018-07-13T09:28:50+02:00 (6 years ago)
Author:
gm
Message:

#1911 (ENHANCE-04): RK3 branche phased with MLF@9937 branche

Location:
NEMO/branches/2018/dev_r9838_ENHANCE04_RK3
Files:
10 edited
1 copied

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/dia25h.F90

    r9598 r9939  
    139139      ! ----------------- 
    140140      ! Define frequency of summing to create 25 h mean 
    141       IF( MOD( 3600,INT(rdt) ) == 0 ) THEN 
    142          i_steps = 3600/INT(rdt) 
     141      IF( MOD( 3600 , INT(rn_Dt) ) == 0 ) THEN 
     142         i_steps = 3600 / INT( rn_Dt ) 
    143143      ELSE 
    144          CALL ctl_stop('STOP', 'dia_wri_tide: timestep must give MOD(3600,rdt) = 0 otherwise no hourly values are possible') 
     144         CALL ctl_stop('STOP', 'dia_wri_tide: timestep must give MOD(3600,rn_Dt) = 0 otherwise no hourly values are possible') 
    145145      ENDIF 
    146146 
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/diaar5.F90

    r9598 r9939  
    161161       
    162162         !                                         ! ocean bottom pressure 
    163          zztmp = rau0 * grav * 1.e-4_wp               ! recover pressure from pressure anomaly and cover to dbar = 1.e4 Pa 
     163         zztmp = rho0 * grav * 1.e-4_wp               ! recover pressure from pressure anomaly and cover to dbar = 1.e4 Pa 
    164164         zbotpres(:,:) = zztmp * ( zbotpres(:,:) + sshn(:,:) + thick0(:,:) ) 
    165165         CALL iom_put( 'botpres', zbotpres ) 
     
    198198         END IF 
    199199         ! 
    200          zmass = rau0 * ( zarho + zvol )                 ! total mass of liquid seawater 
     200         zmass = rho0 * ( zarho + zvol )                 ! total mass of liquid seawater 
    201201         ztemp = ztemp / zvol                            ! potential temperature in liquid seawater 
    202202         zsal  = zsal  / zvol                            ! Salinity of liquid seawater 
     
    239239               DO ji = 1, jpi 
    240240                  DO jj = 1, jpj 
    241                      zpe(ji,jj) = zpe(ji,jj) + avt(ji, jj, jk) * MIN(0._wp,rn2(ji, jj, jk)) * rau0 * e3w_n(ji, jj, jk) 
     241                     zpe(ji,jj) = zpe(ji,jj) + avt(ji, jj, jk) * MIN(0._wp,rn2(ji, jj, jk)) * rho0 * e3w_n(ji, jj, jk) 
    242242                  END DO 
    243243               END DO 
     
    287287       CALL lbc_lnk( z2d, 'U', -1. ) 
    288288       IF( cptr == 'adv' ) THEN 
    289           IF( ktra == jp_tem ) CALL iom_put( "uadv_heattr" , rau0_rcp * z2d )  ! advective heat transport in i-direction 
    290           IF( ktra == jp_sal ) CALL iom_put( "uadv_salttr" , rau0     * z2d )  ! advective salt transport in i-direction 
     289          IF( ktra == jp_tem ) CALL iom_put( "uadv_heattr" , rho0_rcp * z2d )  ! advective heat transport in i-direction 
     290          IF( ktra == jp_sal ) CALL iom_put( "uadv_salttr" , rho0     * z2d )  ! advective salt transport in i-direction 
    291291       ENDIF 
    292292       IF( cptr == 'ldf' ) THEN 
    293           IF( ktra == jp_tem ) CALL iom_put( "udiff_heattr" , rau0_rcp * z2d ) ! diffusive heat transport in i-direction 
    294           IF( ktra == jp_sal ) CALL iom_put( "udiff_salttr" , rau0     * z2d ) ! diffusive salt transport in i-direction 
     293          IF( ktra == jp_tem ) CALL iom_put( "udiff_heattr" , rho0_rcp * z2d ) ! diffusive heat transport in i-direction 
     294          IF( ktra == jp_sal ) CALL iom_put( "udiff_salttr" , rho0     * z2d ) ! diffusive salt transport in i-direction 
    295295       ENDIF 
    296296       ! 
     
    305305       CALL lbc_lnk( z2d, 'V', -1. ) 
    306306       IF( cptr == 'adv' ) THEN 
    307           IF( ktra == jp_tem ) CALL iom_put( "vadv_heattr" , rau0_rcp * z2d )  ! advective heat transport in j-direction 
    308           IF( ktra == jp_sal ) CALL iom_put( "vadv_salttr" , rau0     * z2d )  ! advective salt transport in j-direction 
     307          IF( ktra == jp_tem ) CALL iom_put( "vadv_heattr" , rho0_rcp * z2d )  ! advective heat transport in j-direction 
     308          IF( ktra == jp_sal ) CALL iom_put( "vadv_salttr" , rho0     * z2d )  ! advective salt transport in j-direction 
    309309       ENDIF 
    310310       IF( cptr == 'ldf' ) THEN 
    311           IF( ktra == jp_tem ) CALL iom_put( "vdiff_heattr" , rau0_rcp * z2d ) ! diffusive heat transport in j-direction 
    312           IF( ktra == jp_sal ) CALL iom_put( "vdiff_salttr" , rau0     * z2d ) ! diffusive salt transport in j-direction 
     311          IF( ktra == jp_tem ) CALL iom_put( "vdiff_heattr" , rho0_rcp * z2d ) ! diffusive heat transport in j-direction 
     312          IF( ktra == jp_sal ) CALL iom_put( "vdiff_salttr" , rho0     * z2d ) ! diffusive salt transport in j-direction 
    313313       ENDIF 
    314314           
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/diacfl.F90

    r9598 r9939  
    5555      ! 
    5656      INTEGER :: ji, jj, jk   ! dummy loop indices 
    57       REAL(wp)::   z2dt, zCu_max, zCv_max, zCw_max       ! local scalars 
     57      REAL(wp)::   zCu_max, zCv_max, zCw_max       ! local scalars 
    5858      INTEGER , DIMENSION(3)           ::   iloc_u , iloc_v , iloc_w , iloc   ! workspace 
    5959!!gm this does not work      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zCu_cfl, zCv_cfl, zCw_cfl         ! workspace 
     
    6262      IF( ln_timing )   CALL timing_start('dia_cfl') 
    6363      ! 
    64       !                       ! setup timestep multiplier to account for initial Eulerian timestep 
    65       IF( neuler == 0 .AND. kt == nit000 ) THEN   ;    z2dt = rdt 
    66       ELSE                                        ;    z2dt = rdt * 2._wp 
    67       ENDIF 
    68       ! 
    6964      !                 
    7065      DO jk = 1, jpk       ! calculate Courant numbers 
    7166         DO jj = 1, jpj 
    7267            DO ji = 1, fs_jpim1   ! vector opt. 
    73                zCu_cfl(ji,jj,jk) = ABS( un(ji,jj,jk) ) * z2dt / e1u  (ji,jj)      ! for i-direction 
    74                zCv_cfl(ji,jj,jk) = ABS( vn(ji,jj,jk) ) * z2dt / e2v  (ji,jj)      ! for j-direction 
    75                zCw_cfl(ji,jj,jk) = ABS( wn(ji,jj,jk) ) * z2dt / e3w_n(ji,jj,jk)   ! for k-direction 
     68               zCu_cfl(ji,jj,jk) = ABS( un(ji,jj,jk) ) * rDt / e1u  (ji,jj)      ! for i-direction 
     69               zCv_cfl(ji,jj,jk) = ABS( vn(ji,jj,jk) ) * rDt / e2v  (ji,jj)      ! for j-direction 
     70               zCw_cfl(ji,jj,jk) = ABS( wn(ji,jj,jk) ) * rDt / e3w_n(ji,jj,jk)   ! for k-direction 
    7671            END DO 
    7772         END DO          
     
    120115         WRITE(numcfl,*) '******************************************' 
    121116         WRITE(numcfl,FMT='(3x,a12,6x,f7.4,1x,i4,1x,i4,1x,i4)') 'Run Max Cu', rCu_max, nCu_loc(1), nCu_loc(2), nCu_loc(3) 
    122          WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', z2dt/rCu_max 
     117         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCu_max 
    123118         WRITE(numcfl,*) '******************************************' 
    124119         WRITE(numcfl,FMT='(3x,a12,6x,f7.4,1x,i4,1x,i4,1x,i4)') 'Run Max Cv', rCv_max, nCv_loc(1), nCv_loc(2), nCv_loc(3) 
    125          WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', z2dt/rCv_max 
     120         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCv_max 
    126121         WRITE(numcfl,*) '******************************************' 
    127122         WRITE(numcfl,FMT='(3x,a12,6x,f7.4,1x,i4,1x,i4,1x,i4)') 'Run Max Cw', rCw_max, nCw_loc(1), nCw_loc(2), nCw_loc(3) 
    128          WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', z2dt/rCw_max 
     123         WRITE(numcfl,FMT='(3x,a8,11x,f15.1)') ' => dt/C', rDt/rCw_max 
    129124         CLOSE( numcfl )  
    130125         ! 
     
    133128         WRITE(numout,*) 'dia_cfl : Maximum Courant number information for the run ' 
    134129         WRITE(numout,*) '~~~~~~~' 
    135          WRITE(numout,*) '   Max Cu = ', rCu_max, ' at (i,j,k) = (',nCu_loc(1),nCu_loc(2),nCu_loc(3),') => dt/C = ', z2dt/rCu_max 
    136          WRITE(numout,*) '   Max Cv = ', rCv_max, ' at (i,j,k) = (',nCv_loc(1),nCv_loc(2),nCv_loc(3),') => dt/C = ', z2dt/rCv_max 
    137          WRITE(numout,*) '   Max Cw = ', rCw_max, ' at (i,j,k) = (',nCw_loc(1),nCw_loc(2),nCw_loc(3),') => dt/C = ', z2dt/rCw_max 
     130         WRITE(numout,*) '   Max Cu = ', rCu_max, ' at (i,j,k) = (',nCu_loc(1),nCu_loc(2),nCu_loc(3),') => dt/C = ', rDt/rCu_max 
     131         WRITE(numout,*) '   Max Cv = ', rCv_max, ' at (i,j,k) = (',nCv_loc(1),nCv_loc(2),nCv_loc(3),') => dt/C = ', rDt/rCv_max 
     132         WRITE(numout,*) '   Max Cw = ', rCw_max, ' at (i,j,k) = (',nCw_loc(1),nCw_loc(2),nCw_loc(3),') => dt/C = ', rDt/rCw_max 
    138133      ENDIF 
    139134      ! 
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/diadct.F90

    r9598 r9939  
    679679                  zsn   = interp(k%I,k%J,jk,'V',tsn(:,:,:,jp_sal) )  
    680680                  zrhop = interp(k%I,k%J,jk,'V',rhop)  
    681                   zrhoi = interp(k%I,k%J,jk,'V',rhd*rau0+rau0)  
     681                  zrhoi = interp(k%I,k%J,jk,'V',rhd*rho0+rho0)  
    682682                  zsshn =  0.5*( sshn(k%I,k%J) + sshn(k%I,k%J+1)    ) * vmask(k%I,k%J,1)  
    683683               CASE(2,3)  
     
    685685                  zsn   = interp(k%I,k%J,jk,'U',tsn(:,:,:,jp_sal) )  
    686686                  zrhop = interp(k%I,k%J,jk,'U',rhop)  
    687                   zrhoi = interp(k%I,k%J,jk,'U',rhd*rau0+rau0)  
     687                  zrhoi = interp(k%I,k%J,jk,'U',rhd*rho0+rho0)  
    688688                  zsshn =  0.5*( sshn(k%I,k%J) + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1)   
    689689               END SELECT  
     
    851851                 zsn   = interp(k%I,k%J,jk,'V',tsn(:,:,:,jp_sal) )  
    852852                 zrhop = interp(k%I,k%J,jk,'V',rhop)  
    853                  zrhoi = interp(k%I,k%J,jk,'V',rhd*rau0+rau0)  
     853                 zrhoi = interp(k%I,k%J,jk,'V',rhd*rho0+rho0)  
    854854 
    855855              CASE(2,3)  
     
    857857                 zsn   = interp(k%I,k%J,jk,'U',tsn(:,:,:,jp_sal) )  
    858858                 zrhop = interp(k%I,k%J,jk,'U',rhop)  
    859                  zrhoi = interp(k%I,k%J,jk,'U',rhd*rau0+rau0)  
     859                 zrhoi = interp(k%I,k%J,jk,'U',rhd*rho0+rho0)  
    860860                 zsshn =  0.5*( sshn(k%I,k%J)    + sshn(k%I+1,k%J)    ) * umask(k%I,k%J,1)   
    861861              END SELECT  
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/diaharm.F90

    r9598 r9939  
    181181      IF( kt >= nit000_han .AND. kt <= nitend_han .AND. MOD(kt,nstep_han) == 0 ) THEN 
    182182         ! 
    183          ztime = (kt-nit000+1) * rdt  
     183         ztime = ( kt - nit000+1 ) * rn_Dt  
    184184         ! 
    185185         nhc = 0 
     
    231231      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~' 
    232232 
    233       ztime_ini = nit000_han*rdt                 ! Initial time in seconds at the beginning of analysis 
    234       ztime_end = nitend_han*rdt                 ! Final time in seconds at the end of analysis 
     233      ztime_ini = nit000_han*rn_Dt                 ! Initial time in seconds at the beginning of analysis 
     234      ztime_end = nitend_han*rn_Dt                 ! Final time in seconds at the end of analysis 
    235235      nhan = (nitend_han-nit000_han+1)/nstep_han ! Number of dumps used for analysis 
    236236 
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/diahsb.F90

    r9598 r9939  
    9191      ! 1 - Trends due to forcing ! 
    9292      ! ------------------------- ! 
    93       z_frc_trd_v = r1_rau0 * glob_sum( - ( emp(:,:) - rnf(:,:) + fwfisf(:,:) ) * surf(:,:) )   ! volume fluxes 
     93      z_frc_trd_v = r1_rho0 * glob_sum( - ( emp(:,:) - rnf(:,:) + fwfisf(:,:) ) * surf(:,:) )   ! volume fluxes 
    9494      z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * surf(:,:) )                       ! heat fluxes 
    9595      z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * surf(:,:) )                       ! salt fluxes 
     
    100100      IF( ln_isf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( risf_tsc(:,:,jp_tem) * surf(:,:) ) 
    101101      !                    ! Add penetrative solar radiation 
    102       IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( qsr     (:,:) * surf(:,:) ) 
     102      IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rho0_rcp * glob_sum( qsr     (:,:) * surf(:,:) ) 
    103103      !                    ! Add geothermal heat flux 
    104104      IF( ln_trabbc )   z_frc_trd_t = z_frc_trd_t +               glob_sum( qgh_trd0(:,:) * surf(:,:) ) 
     
    120120      ENDIF 
    121121 
    122       frc_v = frc_v + z_frc_trd_v * rdt 
    123       frc_t = frc_t + z_frc_trd_t * rdt 
    124       frc_s = frc_s + z_frc_trd_s * rdt 
     122      frc_v = frc_v + z_frc_trd_v * rn_Dt 
     123      frc_t = frc_t + z_frc_trd_t * rn_Dt 
     124      frc_s = frc_s + z_frc_trd_s * rn_Dt 
    125125      !                                          ! Advection flux through fixed surface (z=0) 
    126126      IF( ln_linssh ) THEN 
    127          frc_wn_t = frc_wn_t + z_wn_trd_t * rdt 
    128          frc_wn_s = frc_wn_s + z_wn_trd_s * rdt 
     127         frc_wn_t = frc_wn_t + z_wn_trd_t * rn_Dt 
     128         frc_wn_s = frc_wn_s + z_wn_trd_s * rn_Dt 
    129129      ENDIF 
    130130 
     
    196196 
    197197      CALL iom_put(   'bgfrcvol' , frc_v    * 1.e-9    )              ! vol - surface forcing (km3)  
    198       CALL iom_put(   'bgfrctem' , frc_t    * rau0 * rcp * 1.e-20 )   ! hc  - surface forcing (1.e20 J)  
    199       CALL iom_put(   'bgfrchfx' , frc_t    * rau0 * rcp /  &         ! hc  - surface forcing (W/m2)  
    200          &                       ( surf_tot * kt * rdt )        ) 
     198      CALL iom_put(   'bgfrctem' , frc_t    * rho0_rcp * 1.e-20 )     ! hc  - surface forcing (1.e20 J)  
     199      CALL iom_put(   'bgfrchfx' , frc_t    * rho0_rcp /  &           ! hc  - surface forcing (W/m2)  
     200         &                         ( surf_tot * kt * rn_Dt )    ) 
    201201      CALL iom_put(   'bgfrcsal' , frc_s    * 1.e-9    )              ! sc  - surface forcing (psu*km3)  
    202202 
     
    204204         CALL iom_put( 'bgtemper' , zdiff_hc / zvol_tot )              ! Temperature drift     (C)  
    205205         CALL iom_put( 'bgsaline' , zdiff_sc / zvol_tot )              ! Salinity    drift     (PSU) 
    206          CALL iom_put( 'bgheatco' , zdiff_hc * 1.e-20 * rau0 * rcp )   ! Heat content drift    (1.e20 J)  
    207          CALL iom_put( 'bgheatfx' , zdiff_hc * rau0 * rcp /  &         ! Heat flux drift       (W/m2)  
    208             &                       ( surf_tot * kt * rdt )        ) 
     206         CALL iom_put( 'bgheatco' , zdiff_hc * 1.e-20 * rho0_rcp )     ! Heat content drift    (1.e20 J)  
     207         CALL iom_put( 'bgheatfx' , zdiff_hc * rho0_rcp /  &           ! Heat flux drift       (W/m2)  
     208            &                       ( surf_tot * kt * rn_Dt )    ) 
    209209         CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9    )              ! Salt content drift    (psu*km3) 
    210210         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh drift      (km3)   
     
    224224         CALL iom_put( 'bgtemper' , zdiff_hc1 / zvol_tot)              ! Heat content drift    (C)  
    225225         CALL iom_put( 'bgsaline' , zdiff_sc1 / zvol_tot)              ! Salt content drift    (PSU) 
    226          CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rau0 * rcp )  ! Heat content drift    (1.e20 J)  
    227          CALL iom_put( 'bgheatfx' , zdiff_hc1 * rau0 * rcp /  &        ! Heat flux drift       (W/m2)  
    228             &                       ( surf_tot * kt * rdt )         ) 
     226         CALL iom_put( 'bgheatco' , zdiff_hc1 * 1.e-20 * rho0_rcp )    ! Heat content drift    (1.e20 J)  
     227         CALL iom_put( 'bgheatfx' , zdiff_hc1 * rho0_rcp /  &          ! Heat flux drift       (W/m2)  
     228            &                       ( surf_tot * kt * rn_Dt )     ) 
    229229         CALL iom_put( 'bgsaltco' , zdiff_sc1 * 1.e-9    )             ! Salt content drift    (psu*km3) 
    230230         CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9    )              ! volume ssh drift      (km3)   
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/diahth.F90

    r9598 r9939  
    8989      REAL(wp)                         ::   zrho1 = 0.01_wp       ! density     criterion for mixed layer depth 
    9090      REAL(wp)                         ::   ztem2 = 0.2_wp        ! temperature criterion for mixed layer depth 
    91       REAL(wp)                         ::   zthick_0, zcoef       ! temporary scalars 
    92       REAL(wp)                         ::   zztmp, zzdep          ! temporary scalars inside do loop 
    93       REAL(wp)                         ::   zu, zv, zw, zut, zvt  ! temporary workspace 
     91      REAL(wp)                         ::   zthick_0              ! local scalars 
     92      REAL(wp)                         ::   zztmp, zzdep          ! local scalars inside do loop 
     93      REAL(wp)                         ::   zu, zv, zw, zut, zvt  ! local workspace 
    9494      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zabs2      ! MLD: abs( tn - tn(10m) ) = ztem2  
    9595      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ztm2       ! Top of thermocline: tn = tn(10m) - ztem2      
     
    328328      END DO 
    329329      ! from temperature to heat contain 
    330       zcoef = rau0 * rcp 
    331       htc3(:,:) = zcoef * htc3(:,:) 
     330      htc3(:,:) = rho0_rcp * htc3(:,:) 
    332331      CALL iom_put( "hc300", htc3 )      ! first 300m heat content 
    333332      ! 
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/dianam.F90

    r9598 r9939  
    7171      ENDIF 
    7272 
    73       IF( llfsec .OR. kfreq < 0 ) THEN   ;   inbsec = kfreq                       ! output frequency already in seconds 
    74       ELSE                               ;   inbsec = kfreq * NINT( rdt )   ! from time-step to seconds 
     73      IF( llfsec .OR. kfreq < 0 ) THEN   ;   inbsec = kfreq                    ! output frequency already in seconds 
     74      ELSE                               ;   inbsec = kfreq * NINT( rn_Dt )    ! from time-step to seconds 
    7575      ENDIF 
    7676      iddss = NINT( rday          )                                         ! number of seconds in 1 day 
     
    116116      ! date of the beginning and the end of the run 
    117117 
    118       zdrun = rdt / rday * REAL( nitend - nit000, wp )                ! length of the run in days 
    119       zjul  = fjulday - rdt / rday 
     118      zdrun = rn_Dt / rday * REAL( nitend - nit000, wp )              ! length of the run in days 
     119      zjul  = fjulday - rn_Dt / rday 
    120120      CALL ju2ymds( zjul        , iyear1, imonth1, iday1, zsec1 )           ! year/month/day of the beginning of run 
    121121      CALL ju2ymds( zjul + zdrun, iyear2, imonth2, iday2, zsec2 )           ! year/month/day of the end       of run 
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/diaptr.F90

    r9598 r9939  
    5252 
    5353   REAL(wp) ::   rc_sv    = 1.e-6_wp   ! conversion from m3/s to Sverdrup 
    54    REAL(wp) ::   rc_pwatt = 1.e-15_wp  ! conversion from W    to PW (further x rau0 x Cp) 
     54   REAL(wp) ::   rc_pwatt = 1.e-15_wp  ! conversion from W    to PW (further x rho0 x Cp) 
    5555   REAL(wp) ::   rc_ggram = 1.e-6_wp   ! conversion from g    to Pg 
    5656 
     
    424424         IF( dia_ptr_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'dia_ptr_init : unable to allocate arrays' ) 
    425425 
    426          rc_pwatt = rc_pwatt * rau0_rcp          ! conversion from K.s-1 to PetaWatt 
     426         rc_pwatt = rc_pwatt * rho0_rcp          ! conversion from K.s-1 to PetaWatt 
    427427 
    428428         IF( lk_mpp )   CALL mpp_ini_znl( numout )     ! Define MPI communicator for zonal sum 
     
    448448         ! Initialise arrays to zero because diatpr is called before they are first calculated 
    449449         ! Note that this means diagnostics will not be exactly correct when model run is restarted. 
    450          htr_adv(:,:) = 0._wp  ;  str_adv(:,:) =  0._wp  
    451          htr_ldf(:,:) = 0._wp  ;  str_ldf(:,:) =  0._wp  
    452          htr_eiv(:,:) = 0._wp  ;  str_eiv(:,:) =  0._wp  
     450         htr_adv(:,:) = 0._wp  ;   str_adv(:,:) =  0._wp  
     451         htr_ldf(:,:) = 0._wp  ;   str_ldf(:,:) =  0._wp  
     452         htr_eiv(:,:) = 0._wp  ;   str_eiv(:,:) =  0._wp  
    453453         htr_ove(:,:) = 0._wp  ;   str_ove(:,:) =  0._wp 
    454454         htr_btr(:,:) = 0._wp  ;   str_btr(:,:) =  0._wp 
  • NEMO/branches/2018/dev_r9838_ENHANCE04_RK3/src/OCE/DIA/diawri.F90

    r9652 r9939  
    169169 
    170170      IF ( iom_use("taubot") ) THEN                ! bottom stress 
    171          zztmp = rau0 * 0.25 
     171         zztmp = rho0 * 0.25 
    172172         z2d(:,:) = 0._wp 
    173173         DO jj = 2, jpjm1 
     
    212212      IF( iom_use('w_masstr') .OR. iom_use('w_masstr2') ) THEN   ! vertical mass transport & its square value 
    213213         ! Caution: in the VVL case, it only correponds to the baroclinic mass transport. 
    214          z2d(:,:) = rau0 * e1e2t(:,:) 
     214         z2d(:,:) = rho0 * e1e2t(:,:) 
    215215         DO jk = 1, jpk 
    216216            z3d(:,:,jk) = wn(:,:,jk) * z2d(:,:) 
     
    253253            END DO 
    254254         END DO 
    255          CALL iom_put( "heatc", rau0_rcp * z2d )   ! vertically integrated heat content (J/m2) 
     255         CALL iom_put( "heatc", rho0_rcp * z2d )   ! vertically integrated heat content (J/m2) 
    256256      ENDIF 
    257257 
     
    265265            END DO 
    266266         END DO 
    267          CALL iom_put( "saltc", rau0 * z2d )          ! vertically integrated salt content (PSU*kg/m2) 
     267         CALL iom_put( "saltc", rho0 * z2d )          ! vertically integrated salt content (PSU*kg/m2) 
    268268      ENDIF 
    269269      ! 
     
    291291         z2d(:,:) = 0.e0 
    292292         DO jk = 1, jpkm1 
    293             z3d(:,:,jk) = rau0 * un(:,:,jk) * e2u(:,:) * e3u_n(:,:,jk) * umask(:,:,jk) 
     293            z3d(:,:,jk) = rho0 * un(:,:,jk) * e2u(:,:) * e3u_n(:,:,jk) * umask(:,:,jk) 
    294294            z2d(:,:) = z2d(:,:) + z3d(:,:,jk) 
    295295         END DO 
     
    328328         z3d(:,:,jpk) = 0.e0 
    329329         DO jk = 1, jpkm1 
    330             z3d(:,:,jk) = rau0 * vn(:,:,jk) * e1v(:,:) * e3v_n(:,:,jk) * vmask(:,:,jk) 
     330            z3d(:,:,jk) = rho0 * vn(:,:,jk) * e1v(:,:) * e3v_n(:,:,jk) * vmask(:,:,jk) 
    331331         END DO 
    332332         CALL iom_put( "v_masstr", z3d )              ! mass transport in j-direction 
     
    369369         END DO 
    370370         CALL lbc_lnk( z2d, 'T', -1. ) 
    371          CALL iom_put( "tosmint", rau0 * z2d )        ! Vertical integral of temperature 
     371         CALL iom_put( "tosmint", rho0 * z2d )        ! Vertical integral of temperature 
    372372      ENDIF 
    373373      IF( iom_use("somint") ) THEN 
     
    381381         END DO 
    382382         CALL lbc_lnk( z2d, 'T', -1. ) 
    383          CALL iom_put( "somint", rau0 * z2d )         ! Vertical integral of salinity 
     383         CALL iom_put( "somint", rho0 * z2d )         ! Vertical integral of salinity 
    384384      ENDIF 
    385385 
     
    458458      clop = "x"         ! no use of the mask value (require less cpu time and otherwise the model crashes) 
    459459#if defined key_diainstant 
    460       zsto = nwrite * rdt 
     460      zsto = nwrite * rn_Dt 
    461461      clop = "inst("//TRIM(clop)//")" 
    462462#else 
    463       zsto=rdt 
     463      zsto = rn_Dt 
    464464      clop = "ave("//TRIM(clop)//")" 
    465465#endif 
    466       zout = nwrite * rdt 
    467       zmax = ( nitend - nit000 + 1 ) * rdt 
     466      zout = nwrite * rn_Dt 
     467      zmax = ( nitend - nit000 + 1 ) * rn_Dt 
    468468 
    469469      ! Define indices of the horizontal output zoom and vertical limit storage 
     
    485485 
    486486         ! Compute julian date from starting date of the run 
    487          CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian ) 
     487         CALL ymds2ju( nyear, nmonth, nday, rn_Dt, zjulian ) 
    488488         zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment 
    489489         IF(lwp)WRITE(numout,*) 
     
    507507         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
    508508            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
    509             &          nit000-1, zjulian, rdt, nh_T, nid_T, domain_id=nidom, snc4chunks=snc4set ) 
     509            &          nit000-1, zjulian, rn_Dt, nh_T, nid_T, domain_id=nidom, snc4chunks=snc4set ) 
    510510         CALL histvert( nid_T, "deptht", "Vertical T levels",      &  ! Vertical grid: gdept 
    511511            &           "m", ipk, gdept_1d, nz_T, "down" ) 
     
    543543         CALL histbeg( clhstnam, jpi, glamu, jpj, gphiu,           &  ! Horizontal grid: glamu and gphiu 
    544544            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
    545             &          nit000-1, zjulian, rdt, nh_U, nid_U, domain_id=nidom, snc4chunks=snc4set ) 
     545            &          nit000-1, zjulian, rn_Dt, nh_U, nid_U, domain_id=nidom, snc4chunks=snc4set ) 
    546546         CALL histvert( nid_U, "depthu", "Vertical U levels",      &  ! Vertical grid: gdept 
    547547            &           "m", ipk, gdept_1d, nz_U, "down" ) 
     
    556556         CALL histbeg( clhstnam, jpi, glamv, jpj, gphiv,           &  ! Horizontal grid: glamv and gphiv 
    557557            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
    558             &          nit000-1, zjulian, rdt, nh_V, nid_V, domain_id=nidom, snc4chunks=snc4set ) 
     558            &          nit000-1, zjulian, rn_Dt, nh_V, nid_V, domain_id=nidom, snc4chunks=snc4set ) 
    559559         CALL histvert( nid_V, "depthv", "Vertical V levels",      &  ! Vertical grid : gdept 
    560560            &          "m", ipk, gdept_1d, nz_V, "down" ) 
     
    569569         CALL histbeg( clhstnam, jpi, glamt, jpj, gphit,           &  ! Horizontal grid: glamt and gphit 
    570570            &          iimi, iima-iimi+1, ijmi, ijma-ijmi+1,       & 
    571             &          nit000-1, zjulian, rdt, nh_W, nid_W, domain_id=nidom, snc4chunks=snc4set ) 
     571            &          nit000-1, zjulian, rn_Dt, nh_W, nid_W, domain_id=nidom, snc4chunks=snc4set ) 
    572572         CALL histvert( nid_W, "depthw", "Vertical W levels",      &  ! Vertical grid: gdepw 
    573573            &          "m", ipk, gdepw_1d, nz_W, "down" ) 
     
    897897      clname = cdfile_name 
    898898      IF( .NOT. Agrif_Root() ) clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname) 
    899       zsto = rdt 
     899      zsto = rn_Dt 
    900900      clop = "inst(x)"           ! no use of the mask value (require less cpu time) 
    901       zout = rdt 
    902       zmax = ( nitend - nit000 + 1 ) * rdt 
     901      zout = rn_Dt 
     902      zmax = ( nitend - nit000 + 1 ) * rn_Dt 
    903903 
    904904      IF(lwp) WRITE(numout,*) 
     
    912912 
    913913      ! Compute julian date from starting date of the run 
    914       CALL ymds2ju( nyear, nmonth, nday, rdt, zjulian )         ! time axis  
     914      CALL ymds2ju( nyear, nmonth, nday, rn_Dt, zjulian )         ! time axis  
    915915      zjulian = zjulian - adatrj   !   set calendar origin to the beginning of the experiment 
    916916      CALL histbeg( clname, jpi, glamt, jpj, gphit,   & 
    917           1, jpi, 1, jpj, nit000-1, zjulian, rdt, nh_i, id_i, domain_id=nidom, snc4chunks=snc4set ) ! Horizontal grid : glamt and gphit 
     917          1, jpi, 1, jpj, nit000-1, zjulian, rn_Dt, nh_i, id_i, domain_id=nidom, snc4chunks=snc4set ) ! Horizontal grid : glamt and gphit 
    918918      CALL histvert( id_i, "deptht", "Vertical T levels",   &    ! Vertical grid : gdept 
    919919          "m", jpk, gdept_1d, nz_i, "down") 
Note: See TracChangeset for help on using the changeset viewer.