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 13189 for NEMO/branches/2020/dev_r12472_ASINTER-05_Masson_CurrentFeedback/src/OCE/DIA/diaar5.F90 – NEMO

Ignore:
Timestamp:
2020-07-01T11:27:25+02:00 (4 years ago)
Author:
smasson
Message:

dev_r12472_ASINTER-05_Masson_CurrentFeedback: update with trunk@13136, see #2156

Location:
NEMO/branches/2020/dev_r12472_ASINTER-05_Masson_CurrentFeedback
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2020/dev_r12472_ASINTER-05_Masson_CurrentFeedback

    • Property svn:externals
      •  

        old new  
        88 
        99# SETTE 
        10 ^/utils/CI/sette@HEAD         sette 
         10^/utils/CI/sette@12931        sette 
  • NEMO/branches/2020/dev_r12472_ASINTER-05_Masson_CurrentFeedback/src/OCE/DIA/diaar5.F90

    r12495 r13189  
    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 
     
    5453      !!---------------------------------------------------------------------- 
    5554      ! 
    56       ALLOCATE( area(jpi,jpj), thick0(jpi,jpj) , sn0(jpi,jpj,jpk) , STAT=dia_ar5_alloc ) 
     55      ALLOCATE( thick0(jpi,jpj) , sn0(jpi,jpj,jpk) , STAT=dia_ar5_alloc ) 
    5756      ! 
    5857      CALL mpp_sum ( 'diaar5', dia_ar5_alloc ) 
     
    7877      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: zarea_ssh , zbotpres       ! 2D workspace  
    7978      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     :: zpe, z2d                   ! 2D workspace  
    80       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   :: zrhd , zrhop, ztpot   ! 3D workspace 
     79      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   :: zrhd , ztpot               ! 3D workspace 
    8180      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: ztsn                       ! 4D workspace 
    8281 
     
    8887      IF( l_ar5 ) THEN  
    8988         ALLOCATE( zarea_ssh(jpi,jpj), zbotpres(jpi,jpj), z2d(jpi,jpj) ) 
    90          ALLOCATE( zrhd(jpi,jpj,jpk) , zrhop(jpi,jpj,jpk) ) 
     89         ALLOCATE( zrhd(jpi,jpj,jpk) ) 
    9190         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(:,:) ) 
     91         zarea_ssh(:,:) = e1e2t(:,:) * ssh(:,:,Kmm) 
     92      ENDIF 
     93      ! 
     94      CALL iom_put( 'e2u'      , e2u  (:,:) ) 
     95      CALL iom_put( 'e1v'      , e1v  (:,:) ) 
     96      CALL iom_put( 'areacello', e1e2t(:,:) ) 
    9897      ! 
    9998      IF( iom_use( 'volcello' ) .OR. iom_use( 'masscello' )  ) THEN   
    10099         zrhd(:,:,jpk) = 0._wp        ! ocean volume ; rhd is used as workspace 
    101100         DO jk = 1, jpkm1 
    102             zrhd(:,:,jk) = area(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
     101            zrhd(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk) 
    103102         END DO 
    104103         CALL iom_put( 'volcello'  , zrhd(:,:,:)  )  ! WARNING not consistent with CMIP DR where volcello is at ca. 2000 
     
    151150         END IF 
    152151         !                                          
    153          zarho = glob_sum( 'diaar5', area(:,:) * zbotpres(:,:) )  
     152         zarho = glob_sum( 'diaar5', e1e2t(:,:) * zbotpres(:,:) )  
    154153         zssh_steric = - zarho / area_tot 
    155154         CALL iom_put( 'sshthster', zssh_steric ) 
    156155       
    157156         !                                         ! steric sea surface height 
    158          CALL eos( ts(:,:,:,:,Kmm), zrhd, zrhop, gdept(:,:,:,Kmm) )                 ! now in situ and potential density 
    159          zrhop(:,:,jpk) = 0._wp 
    160          CALL iom_put( 'rhop', zrhop ) 
    161          ! 
    162157         zbotpres(:,:) = 0._wp                        ! no atmospheric surface pressure, levitating sea-ice 
    163158         DO jk = 1, jpkm1 
    164             zbotpres(:,:) = zbotpres(:,:) + e3t(:,:,jk,Kmm) * zrhd(:,:,jk) 
     159            zbotpres(:,:) = zbotpres(:,:) + e3t(:,:,jk,Kmm) * rhd(:,:,jk) 
    165160         END DO 
    166161         IF( ln_linssh ) THEN 
     
    169164                  DO jj = 1,jpj 
    170165                     iks = mikt(ji,jj) 
    171                      zbotpres(ji,jj) = zbotpres(ji,jj) + ssh(ji,jj,Kmm) * zrhd(ji,jj,iks) + riceload(ji,jj) 
     166                     zbotpres(ji,jj) = zbotpres(ji,jj) + ssh(ji,jj,Kmm) * rhd(ji,jj,iks) + riceload(ji,jj) 
    172167                  END DO 
    173168               END DO 
    174169            ELSE 
    175                zbotpres(:,:) = zbotpres(:,:) + ssh(:,:,Kmm) * zrhd(:,:,1) 
     170               zbotpres(:,:) = zbotpres(:,:) + ssh(:,:,Kmm) * rhd(:,:,1) 
    176171            END IF 
    177172         END IF 
    178173         !     
    179          zarho = glob_sum( 'diaar5', area(:,:) * zbotpres(:,:) )  
     174         zarho = glob_sum( 'diaar5', e1e2t(:,:) * zbotpres(:,:) )  
    180175         zssh_steric = - zarho / area_tot 
    181176         CALL iom_put( 'sshsteric', zssh_steric ) 
     
    191186          ztsn(:,:,:,:) = 0._wp                    ! ztsn(:,:,1,jp_tem/sal) is used here as 2D Workspace for temperature & salinity 
    192187          DO_3D_11_11( 1, jpkm1 ) 
    193              zztmp = area(ji,jj) * e3t(ji,jj,jk,Kmm) 
     188             zztmp = e1e2t(ji,jj) * e3t(ji,jj,jk,Kmm) 
    194189             ztsn(ji,jj,1,jp_tem) = ztsn(ji,jj,1,jp_tem) + zztmp * ts(ji,jj,jk,jp_tem,Kmm) 
    195190             ztsn(ji,jj,1,jp_sal) = ztsn(ji,jj,1,jp_sal) + zztmp * ts(ji,jj,jk,jp_sal,Kmm) 
     
    237232               z2d(:,:) = 0._wp 
    238233               DO jk = 1, jpkm1 
    239                  z2d(:,:) = z2d(:,:) + area(:,:) * e3t(:,:,jk,Kmm) * ztpot(:,:,jk) 
     234                 z2d(:,:) = z2d(:,:) + e1e2t(:,:) * e3t(:,:,jk,Kmm) * ztpot(:,:,jk) 
    240235               END DO 
    241236               ztemp = glob_sum( 'diaar5', z2d(:,:)  )  
     
    244239             ! 
    245240             IF( iom_use( 'ssttot' ) ) THEN   ! Output potential temperature in case we use TEOS-10 
    246                zsst = glob_sum( 'diaar5',  area(:,:) * ztpot(:,:,1)  )  
     241               zsst = glob_sum( 'diaar5',  e1e2t(:,:) * ztpot(:,:,1)  )  
    247242               CALL iom_put( 'ssttot', zsst / area_tot ) 
    248243             ENDIF 
     
    259254      ELSE        
    260255         IF( iom_use('ssttot') ) THEN   ! Output sst in case we use EOS-80 
    261             zsst  = glob_sum( 'diaar5', area(:,:) * ts(:,:,1,jp_tem,Kmm) ) 
     256            zsst  = glob_sum( 'diaar5', e1e2t(:,:) * ts(:,:,1,jp_tem,Kmm) ) 
    262257            CALL iom_put('ssttot', zsst / area_tot ) 
    263258         ENDIF 
     
    294289      IF( l_ar5 ) THEN 
    295290        DEALLOCATE( zarea_ssh , zbotpres, z2d ) 
    296         DEALLOCATE( zrhd      , zrhop    ) 
    297291        DEALLOCATE( ztsn                 ) 
    298292      ENDIF 
     
    368362      IF(   iom_use( 'voltot'  ) .OR. iom_use( 'sshtot'    )  .OR. iom_use( 'sshdyn' )  .OR.  &  
    369363         &  iom_use( 'masstot' ) .OR. iom_use( 'temptot'   )  .OR. iom_use( 'saltot' ) .OR.  &     
    370          &  iom_use( 'botpres' ) .OR. iom_use( 'sshthster' )  .OR. iom_use( 'sshsteric' )  ) L_ar5 = .TRUE. 
     364         &  iom_use( 'botpres' ) .OR. iom_use( 'sshthster' )  .OR. iom_use( 'sshsteric' ) .OR. & 
     365         &  iom_use( 'rhop' )  ) L_ar5 = .TRUE. 
    371366   
    372367      IF( l_ar5 ) THEN 
     
    375370         IF( dia_ar5_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'dia_ar5_init : unable to allocate arrays' ) 
    376371 
    377          area(:,:) = e1e2t(:,:) 
    378          area_tot  = glob_sum( 'diaar5', area(:,:) ) 
     372         area_tot  = glob_sum( 'diaar5', e1e2t(:,:) ) 
    379373 
    380374         ALLOCATE( zvol0(jpi,jpj) ) 
     
    383377         DO_3D_11_11( 1, jpkm1 ) 
    384378            idep = tmask(ji,jj,jk) * e3t_0(ji,jj,jk) 
    385             zvol0 (ji,jj) = zvol0 (ji,jj) +  idep * area(ji,jj) 
     379            zvol0 (ji,jj) = zvol0 (ji,jj) +  idep * e1e2t(ji,jj) 
    386380            thick0(ji,jj) = thick0(ji,jj) +  idep     
    387381         END_3D 
Note: See TracChangeset for help on using the changeset viewer.