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 15602 for NEMO/branches/UKMO/NEMO_4.0.4_FOAM_pcbias/src/OCE/DYN/dynhpg.F90 – NEMO

Ignore:
Timestamp:
2021-12-16T10:11:36+01:00 (3 years ago)
Author:
jenniewaters
Message:

Code changes to get pcbias working.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/UKMO/NEMO_4.0.4_FOAM_pcbias/src/OCE/DYN/dynhpg.F90

    r14075 r15602  
    4646   USE timing          ! Timing 
    4747   USE iom 
     48   USE biaspar         ! bias correction variables 
    4849 
    4950   IMPLICIT NONE 
     
    9293      !!---------------------------------------------------------------------- 
    9394      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    94       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::   ztrdu, ztrdv 
     95      INTEGER                                   ::   ji, jj, jk                 ! dummy loop indices 
     96      INTEGER                                   ::   iku, ikv                   ! k indices for bottom level at u and v points 
     97      INTEGER                                   ::   numf 
     98      REAL(wp), POINTER, DIMENSION(:,:,:)       ::   ztrdu, ztrdv 
     99      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::   z_rhd_st, z_rhd_diff       ! tmp density storage for pressure corr 
     100      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::   z_ua, z_va                 ! tmp store for ua and va including hpg but not pressure correction  
     101      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::   z_ua_bpc, z_va_bpc         ! ua calculated with bias pressure correction   
     102      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     ::   z_ua_bpc_bot, z_va_bpc_bot ! bias pc fields calculated at the ocean bottom 
    95103      !!---------------------------------------------------------------------- 
    96104      ! 
     
    102110         ztrdv(:,:,:) = va(:,:,:) 
    103111      ENDIF 
     112      ! 
     113      IF ( ln_bias .AND. ln_bias_pc_app ) THEN 
     114 
     115         ! allocate space for tempory variables for the bias pressure correction (bpc) 
     116         ALLOCATE( z_rhd_st(jpi,jpj,jpk), & 
     117            &      z_ua(jpi,jpj,jpk),     & 
     118            &      z_va(jpi,jpj,jpk),     &   
     119            &      z_ua_bpc(jpi,jpj,jpk), & 
     120            &      z_va_bpc(jpi,jpj,jpk), &  
     121            &      z_ua_bpc_bot(jpi,jpj), & 
     122            &      z_va_bpc_bot(jpi,jpj), &  
     123       &      z_rhd_diff(jpi,jpj,jpk)& 
     124            &    ) 
     125 
     126         ! save the original acceleration trends  
     127         ! (z_ua_bpc, z_va_bpc are used as temporary storage) 
     128         z_ua_bpc(:,:,:)     = ua(:,:,:) 
     129         z_va_bpc(:,:,:)     = va(:,:,:) 
     130          
     131      END IF 
    104132      ! 
    105133      SELECT CASE ( nhpg )      ! Hydrostatic pressure gradient computation 
     
    112140      END SELECT 
    113141      ! 
     142      IF ( ln_bias .AND. ln_bias_pc_app ) THEN 
     143 
     144         ! The aim here is to calculate the contribution of the bpc to the acceleration terms. 
     145         ! This is done so that the effect of the bpc on the hpg at the bottom can be removed. 
     146         ! In order to do that: 
     147         !    1. The hpg calculation is done again, but with the contributions of the bpc included. 
     148         !    2. The difference between the acceleration terms (w and w/o bpc) is then calculated. 
     149         !    3. The effect of the bpc on the bottom hpg is then removed. 
     150         !    4. The total change to the acceleration terms is then calculated. 
     151          
     152         ! The original density field (without the bpc) is stored.           
     153         z_rhd_st(:,:,:) = rhd(:,:,:) 
     154 
     155         ! Set the density used in the hpc calculations to the value including the effect of the bpc. 
     156         rhd(:,:,:)      = rhd_pc(:,:,:)  
     157             
     158         ! save the acceleration trends including hpg field but calculated without the bpc fields 
     159         z_ua(:,:,:)     = ua(:,:,:) 
     160         z_va(:,:,:)     = va(:,:,:) 
     161 
     162         ! reset the acceleration trends to their original values 
     163         ua(:,:,:)       = z_ua_bpc(:,:,:)     
     164         va(:,:,:)       = z_va_bpc(:,:,:)   
     165 
     166         ! re-calculate the horizontal pressure gradients with the bpc fields  
     167         SELECT CASE ( nhpg )      ! Hydrostatic pressure gradient computation 
     168         CASE (  np_zco )   ;   CALL hpg_zco    ( kt )      ! z-coordinate 
     169         CASE (  np_zps )   ;   CALL hpg_zps    ( kt )      ! z-coordinate plus partial steps (interpolation) 
     170         CASE (  np_sco )   ;   CALL hpg_sco    ( kt )      ! s-coordinate (standard jacobian formulation) 
     171         CASE (  np_djc )   ;   CALL hpg_djc    ( kt )      ! s-coordinate (Density Jacobian with Cubic polynomial) 
     172         CASE (  np_prj )   ;   CALL hpg_prj    ( kt )      ! s-coordinate (Pressure Jacobian scheme) 
     173         CASE (  np_isf )   ;   CALL hpg_isf    ( kt )      ! s-coordinate similar to sco modify for ice shelf 
     174         END SELECT 
     175 
     176         ! calculate the bpc contribution to ua and va 
     177         z_ua_bpc(:,:,:) = ua(:,:,:) - z_ua(:,:,:) 
     178         z_va_bpc(:,:,:) = va(:,:,:) - z_va(:,:,:) 
     179 
     180         ! calculate the bpc contribution to ua and va at the bottom  
     181         DO jj = 2, jpjm1 
     182            DO ji = 2, jpim1 
     183               iku = mbku(ji,jj) 
     184               ikv = mbkv(ji,jj)  
     185               z_ua_bpc_bot(ji,jj) = z_ua_bpc(ji,jj,iku) 
     186               z_va_bpc_bot(ji,jj) = z_va_bpc(ji,jj,ikv) 
     187            END DO  ! ji 
     188         END DO ! jj 
     189 
     190         ! subtract off the bottom values of bpc contribution to ua and va  
     191         DO jk = 1, jpk - 1 
     192            z_ua_bpc(:,:,jk) = z_ua_bpc(:,:,jk) - z_ua_bpc_bot(:,:) 
     193            z_va_bpc(:,:,jk) = z_va_bpc(:,:,jk) - z_va_bpc_bot(:,:) 
     194         END DO  
     195 
     196         ! calculate ua using the original hpg (z_ua) and the bias hpg  
     197         ! with the bottom pressure gradients subtracted off  
     198         ua(:,:,:) = z_ua(:,:,:) + z_ua_bpc(:,:,:) 
     199         va(:,:,:) = z_va(:,:,:) + z_va_bpc(:,:,:) 
     200 
     201         ! restore original density field 
     202         rhd(:,:,:) = z_rhd_st(:,:,:)      
     203 
     204         ! deallocate tempory variables 
     205         DEALLOCATE( z_rhd_st, z_ua, z_va, z_ua_bpc,   & 
     206            &        z_va_bpc, z_ua_bpc_bot,           & 
     207            &        z_va_bpc_bot, z_rhd_diff          & 
     208            &                                          ) 
     209        
     210      ENDIF  ! ln_bias .AND. ln_bias_pc_app 
     211 
     212 
    114213      IF( l_trddyn ) THEN      ! save the hydrostatic pressure gradient trends for momentum trend diagnostics 
    115214         ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:) 
Note: See TracChangeset for help on using the changeset viewer.