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 13151 for NEMO/branches/2020/dev_r12527_Gurvan_ShallowWater/src/OCE/DIA/diaar5.F90 – NEMO

Ignore:
Timestamp:
2020-06-24T14:38:26+02:00 (4 years ago)
Author:
gm
Message:

result from merge with qco r12983

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12527_Gurvan_ShallowWater/src/OCE/DIA/diaar5.F90

    r12489 r13151  
    3232   REAL(wp)                         ::   vol0         ! ocean volume (interior domain) 
    3333   REAL(wp)                         ::   area_tot     ! total ocean surface (interior domain) 
    34    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:  ) ::   area         ! cell surface (interior domain) 
    3534   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:  ) ::   thick0       ! ocean thickness (interior domain) 
    3635   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sn0          ! initial salinity 
     
    4039   !! * Substitutions 
    4140#  include "do_loop_substitute.h90" 
     41#  include "domzgr_substitute.h90" 
    4242   !!---------------------------------------------------------------------- 
    4343   !! NEMO/OCE 4.0 , NEMO Consortium (2018) 
     
    5454      !!---------------------------------------------------------------------- 
    5555      ! 
    56       ALLOCATE( area(jpi,jpj), thick0(jpi,jpj) , sn0(jpi,jpj,jpk) , STAT=dia_ar5_alloc ) 
     56      ALLOCATE( thick0(jpi,jpj) , sn0(jpi,jpj,jpk) , STAT=dia_ar5_alloc ) 
    5757      ! 
    5858      CALL mpp_sum ( 'diaar5', dia_ar5_alloc ) 
     
    7777      ! 
    7878      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: zarea_ssh , zbotpres       ! 2D workspace  
    79       REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: zpe, z2d                   ! 2D workspace  
    80       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   :: zrhd , zrhop, ztpot   ! 3D workspace 
     79      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: z2d, zpe                   ! 2D workspace  
     80      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   :: z3d, zrhd , zrhop, ztpot, zgdept   ! 3D workspace (zgdept: needed to use the substitute) 
    8181      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: ztsn                       ! 4D workspace 
    8282 
     
    9090         ALLOCATE( zrhd(jpi,jpj,jpk) , zrhop(jpi,jpj,jpk) ) 
    9191         ALLOCATE( ztsn(jpi,jpj,jpk,jpts) ) 
    92          zarea_ssh(:,:) = area(:,:) * ssh(:,:,Kmm) 
    93       ENDIF 
    94       ! 
    95       CALL iom_put( 'e2u'      , e2u (:,:) ) 
    96       CALL iom_put( 'e1v'      , e1v (:,:) ) 
    97       CALL iom_put( 'areacello', area(:,:) ) 
     92         zarea_ssh(:,:) = e1e2t(:,:) * ssh(:,:,Kmm) 
     93      ENDIF 
     94      ! 
     95      CALL iom_put( 'e2u'      , e2u  (:,:) ) 
     96      CALL iom_put( 'e1v'      , e1v  (:,:) ) 
     97      CALL iom_put( 'areacello', e1e2t(:,:) ) 
    9898      ! 
    9999      IF( iom_use( 'volcello' ) .OR. iom_use( 'masscello' )  ) THEN   
    100100         zrhd(:,:,jpk) = 0._wp        ! ocean volume ; rhd is used as workspace 
    101101         DO jk = 1, jpkm1 
    102             zrhd(:,:,jk) = area(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
     102            zrhd(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    103103         END DO 
     104         DO jk = 1, jpk 
     105            z3d(:,:,jk) =  rho0 * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
     106         END DO  
    104107         CALL iom_put( 'volcello'  , zrhd(:,:,:)  )  ! WARNING not consistent with CMIP DR where volcello is at ca. 2000 
    105          CALL iom_put( 'masscello' , rho0 * e3t(:,:,:,Kmm) * tmask(:,:,:) )  ! ocean mass 
     108         CALL iom_put( 'masscello' , z3d (:,:,:) )   ! ocean mass 
    106109      ENDIF  
    107110      ! 
     
    129132         ztsn(:,:,:,jp_tem) = ts(:,:,:,jp_tem,Kmm)                    ! thermosteric ssh 
    130133         ztsn(:,:,:,jp_sal) = sn0(:,:,:) 
    131          CALL eos( ztsn, zrhd, gdept(:,:,:,Kmm) )                       ! now in situ density using initial salinity 
     134         DO jk = 1, jpk 
     135            zgdept(:,:,jk) = gdept(:,:,jk,Kmm) 
     136         END DO 
     137         CALL eos( ztsn, zrhd, zgdept)                       ! now in situ density using initial salinity 
    132138         ! 
    133139         zbotpres(:,:) = 0._wp                        ! no atmospheric surface pressure, levitating sea-ice 
     
    151157         END IF 
    152158         !                                          
    153          zarho = glob_sum( 'diaar5', area(:,:) * zbotpres(:,:) )  
     159         zarho = glob_sum( 'diaar5', e1e2t(:,:) * zbotpres(:,:) )  
    154160         zssh_steric = - zarho / area_tot 
    155161         CALL iom_put( 'sshthster', zssh_steric ) 
    156162       
    157163         !                                         ! steric sea surface height 
    158          CALL eos( ts(:,:,:,:,Kmm), zrhd, zrhop, gdept(:,:,:,Kmm) )                 ! now in situ and potential density 
     164         CALL eos( ts(:,:,:,:,Kmm), zrhd, zrhop, zgdept )                 ! now in situ and potential density 
    159165         zrhop(:,:,jpk) = 0._wp 
    160166         CALL iom_put( 'rhop', zrhop ) 
     
    177183         END IF 
    178184         !     
    179          zarho = glob_sum( 'diaar5', area(:,:) * zbotpres(:,:) )  
     185         zarho = glob_sum( 'diaar5', e1e2t(:,:) * zbotpres(:,:) )  
    180186         zssh_steric = - zarho / area_tot 
    181187         CALL iom_put( 'sshsteric', zssh_steric ) 
     
    191197          ztsn(:,:,:,:) = 0._wp                    ! ztsn(:,:,1,jp_tem/sal) is used here as 2D Workspace for temperature & salinity 
    192198          DO_3D_11_11( 1, jpkm1 ) 
    193              zztmp = area(ji,jj) * e3t(ji,jj,jk,Kmm) 
     199             zztmp = e1e2t(ji,jj) * e3t(ji,jj,jk,Kmm) 
    194200             ztsn(ji,jj,1,jp_tem) = ztsn(ji,jj,1,jp_tem) + zztmp * ts(ji,jj,jk,jp_tem,Kmm) 
    195201             ztsn(ji,jj,1,jp_sal) = ztsn(ji,jj,1,jp_sal) + zztmp * ts(ji,jj,jk,jp_sal,Kmm) 
     
    237243               z2d(:,:) = 0._wp 
    238244               DO jk = 1, jpkm1 
    239                  z2d(:,:) = z2d(:,:) + area(:,:) * e3t(:,:,jk,Kmm) * ztpot(:,:,jk) 
     245                 z2d(:,:) = z2d(:,:) + e1e2t(:,:) * e3t(:,:,jk,Kmm) * ztpot(:,:,jk) 
    240246               END DO 
    241247               ztemp = glob_sum( 'diaar5', z2d(:,:)  )  
     
    244250             ! 
    245251             IF( iom_use( 'ssttot' ) ) THEN   ! Output potential temperature in case we use TEOS-10 
    246                zsst = glob_sum( 'diaar5',  area(:,:) * ztpot(:,:,1)  )  
     252               zsst = glob_sum( 'diaar5',  e1e2t(:,:) * ztpot(:,:,1)  )  
    247253               CALL iom_put( 'ssttot', zsst / area_tot ) 
    248254             ENDIF 
     
    259265      ELSE        
    260266         IF( iom_use('ssttot') ) THEN   ! Output sst in case we use EOS-80 
    261             zsst  = glob_sum( 'diaar5', area(:,:) * ts(:,:,1,jp_tem,Kmm) ) 
     267            zsst  = glob_sum( 'diaar5', e1e2t(:,:) * ts(:,:,1,jp_tem,Kmm) ) 
    262268            CALL iom_put('ssttot', zsst / area_tot ) 
    263269         ENDIF 
     
    375381         IF( dia_ar5_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'dia_ar5_init : unable to allocate arrays' ) 
    376382 
    377          area(:,:) = e1e2t(:,:) 
    378          area_tot  = glob_sum( 'diaar5', area(:,:) ) 
     383         area_tot  = glob_sum( 'diaar5', e1e2t(:,:) ) 
    379384 
    380385         ALLOCATE( zvol0(jpi,jpj) ) 
     
    383388         DO_3D_11_11( 1, jpkm1 ) 
    384389            idep = tmask(ji,jj,jk) * e3t_0(ji,jj,jk) 
    385             zvol0 (ji,jj) = zvol0 (ji,jj) +  idep * area(ji,jj) 
     390            zvol0 (ji,jj) = zvol0 (ji,jj) +  idep * e1e2t(ji,jj) 
    386391            thick0(ji,jj) = thick0(ji,jj) +  idep     
    387392         END_3D 
Note: See TracChangeset for help on using the changeset viewer.