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 11556 for branches – NEMO

Changeset 11556 for branches


Ignore:
Timestamp:
2019-09-17T14:55:54+02:00 (5 years ago)
Author:
mattmartin
Message:

Commit changes to bias pressure correction from ticket https://code.metoffice.gov.uk/trac/utils/ticket/262.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_GO6_package_FOAMv14/NEMOGCM/NEMO/OPA_SRC/DYN/dynhpg.F90

    r8447 r11556  
    1717   !!                 !           (A. Coward) suppression of hel, wdj and rot options 
    1818   !!            3.6  !  2014-11  (P. Mathiot) hpg_isf: original code for ice shelf cavity 
     19   !!            3.6  !  2019-08  (M. Bell) Revisions to bias pressure correction  
    1920   !!---------------------------------------------------------------------- 
    2021 
     
    8485      !!---------------------------------------------------------------------- 
    8586      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    86       REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdu, ztrdv 
    87       REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::   z_rhd_st  ! tmp density storage for pressure corr 
    88       REAL(wp), ALLOCATABLE, DIMENSION(:,:)     ::   z_gru_st  ! tmp ua trends storage for pressure corr 
    89       REAL(wp), ALLOCATABLE, DIMENSION(:,:)     ::   z_grv_st  ! tmp va trends storage for pressure corr 
     87      INTEGER                                   ::   ji, jj, jk                 ! dummy loop indices 
     88      INTEGER                                   ::   iku, ikv                   ! k indices for bottom level at u and v points 
     89      REAL(wp), POINTER, DIMENSION(:,:,:)       ::   ztrdu, ztrdv 
     90      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::   z_rhd_st                   ! tmp density storage for pressure corr 
     91      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::   z_ua, z_va                 ! tmp store for ua and va including hpg but not pressure correction  
     92      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:)   ::   z_ua_bpc, z_va_bpc         ! ua calculated with bias pressure correction   
     93      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     ::   z_gru_st, z_grv_st         ! tmp ua and va trends storage for pressure corr 
     94      REAL(wp), ALLOCATABLE, DIMENSION(:,:)     ::   z_ua_bpc_bot, z_va_bpc_bot ! bias pc fields calculated at the ocean bottom 
     95       
    9096      !!---------------------------------------------------------------------- 
    9197      ! 
     
    98104      ENDIF 
    99105      ! 
     106 
    100107      IF ( ln_bias .AND. ln_bias_pc_app ) THEN 
    101108 
    102          !Allocate space for tempory variables 
     109         ! allocate space for tempory variables for the bias pressure correction (bpc) 
    103110         ALLOCATE( z_rhd_st(jpi,jpj,jpk), & 
    104111            &      z_gru_st(jpi,jpj),     & 
    105             &      z_grv_st(jpi,jpj)      ) 
    106  
    107          z_rhd_st(:,:,:) = rhd(:,:,:)     ! store orig density  
    108          rhd(:,:,:)      = rhd_pc(:,:,:)  ! use pressure corrected density 
    109          z_gru_st(:,:)   = gru(:,:) 
    110          gru(:,:)        = gru_pc(:,:) 
    111          z_grv_st(:,:)   = grv(:,:) 
    112          grv(:,:)        = grv_pc(:,:) 
    113  
    114       ENDIF 
     112            &      z_grv_st(jpi,jpj),     & 
     113            &      z_ua(jpi,jpj,jpk),     & 
     114            &      z_va(jpi,jpj,jpk),     &   
     115            &      z_ua_bpc(jpi,jpj,jpk), & 
     116            &      z_va_bpc(jpi,jpj,jpk), &  
     117            &      z_ua_bpc_bot(jpi,jpj), & 
     118            &      z_va_bpc_bot(jpi,jpj)  &  
     119            &    ) 
     120 
     121         ! save the original acceleration trends  
     122         ! (z_ua_bpc, z_va_bpc are used as temporary storage) 
     123         z_ua_bpc(:,:,:)     = ua(:,:,:) 
     124         z_va_bpc(:,:,:)     = va(:,:,:) 
     125          
     126      END IF  
    115127 
    116128      SELECT CASE ( nhpg )      ! Hydrostatic pressure gradient computation 
     
    123135      END SELECT 
    124136      ! 
     137 
     138      IF ( ln_bias .AND. ln_bias_pc_app ) THEN 
     139 
     140         ! The aim here is to calculate the contribution of the bpc to the acceleration terms. 
     141         ! This is done so that the effect of the bpc on the hpg at the bottom can be removed. 
     142         ! In order to do that: 
     143         !    1. The hpg calculation is done again, but with the contributions of the bpc included. 
     144         !    2. The difference between the acceleration terms (w and w/o bpc) is then calculated. 
     145         !    3. The effect of the bpc on the bottom hpg is then removed. 
     146         !    4. The total change to the acceleration terms is then calculated. 
     147          
     148         ! The original density fields etc (without the bpc) are stored.           
     149         z_rhd_st(:,:,:) = rhd(:,:,:) 
     150         z_gru_st(:,:)   = gru(:,:) 
     151         z_grv_st(:,:)   = grv(:,:) 
     152 
     153         ! Set the density etc used in the hpc calculations to the value including the effect of the bpc. 
     154         rhd(:,:,:)      = rhd_pc(:,:,:) 
     155         gru(:,:)        = gru_pc(:,:)    
     156         grv(:,:)        = grv_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 (  0 )   ;   CALL hpg_zco    ( kt )      ! z-coordinate 
     169         CASE (  1 )   ;   CALL hpg_zps    ( kt )      ! z-coordinate plus partial steps (interpolation) 
     170         CASE (  2 )   ;   CALL hpg_sco    ( kt )      ! s-coordinate (standard jacobian formulation) 
     171         CASE (  3 )   ;   CALL hpg_djc    ( kt )      ! s-coordinate (Density Jacobian with Cubic polynomial) 
     172         CASE (  4 )   ;   CALL hpg_prj    ( kt )      ! s-coordinate (Pressure Jacobian scheme) 
     173         CASE (  5 )   ;   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, gru and grv fields  
     202         rhd(:,:,:) = z_rhd_st(:,:,:)      
     203         gru(:,:)   = z_gru_st(:,:) 
     204         grv(:,:)   = z_grv_st(:,:) 
     205 
     206         ! deallocate tempory variables 
     207         DEALLOCATE( z_rhd_st,   z_gru_st, z_grv_st,   & 
     208            &        z_ua, z_va, z_ua_bpc, z_va_bpc,   & 
     209            &        z_ua_bpc_bot, z_va_bpc_bot        & 
     210            &                                          ) 
     211        
     212      ENDIF  ! ln_bias .AND. ln_bias_pc_app 
     213 
     214 
    125215      IF( l_trddyn ) THEN      ! save the hydrostatic pressure gradient trends for momentum trend diagnostics 
    126216         ztrdu(:,:,:) = ua(:,:,:) - ztrdu(:,:,:) 
     
    132222      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ua, clinfo1=' hpg  - Ua: ', mask1=umask,   & 
    133223         &                       tab3d_2=va, clinfo2=       ' Va: ', mask2=vmask, clinfo3='dyn' ) 
    134       ! 
    135       IF ( ln_bias .AND. ln_bias_pc_app )  THEN 
    136          IF(lwp) THEN  
    137          WRITE(numout,*) " ! restore original density" 
    138          ENDIF 
    139          rhd(:,:,:) = z_rhd_st(:,:,:)     ! restore original density 
    140          gru(:,:)   = z_gru_st(:,:) 
    141          grv(:,:)   = z_grv_st(:,:) 
    142  
    143          !Deallocate tempory variables 
    144          DEALLOCATE( z_rhd_st,     & 
    145             &        z_gru_st,     & 
    146             &        z_grv_st      ) 
    147       ENDIF 
    148224      ! 
    149225      IF( nn_timing == 1 )  CALL timing_stop('dyn_hpg') 
Note: See TracChangeset for help on using the changeset viewer.