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 6328 – NEMO

Changeset 6328


Ignore:
Timestamp:
2016-02-18T17:46:36+01:00 (8 years ago)
Author:
jenniewaters
Message:

Make reviewer suggested changes. Update code to allow key_bias to be removed. Fixe a few minor bugs.

Location:
branches/UKMO/dev_r5518_pcbias/NEMOGCM
Files:
7 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_pcbias/NEMOGCM/CONFIG/SHARED/namelist_ref

    r6300 r6328  
    13021302&nambias   ! Bias pressure correctiom 
    13031303!----------------------------------------------------------------------- 
    1304    ln_bias = .false. 
     1304   ln_bias        = .false. 
    13051305   ln_bias_asm    = .false. 
    13061306   ln_bias_rlx    = .false. 
    13071307   ln_bias_ofl    = .false. 
    13081308   ln_bias_ts_app = .false. 
    1309    ln_bias_pc_app = .false. 
    1310    eft_asm        = 90.     
    1311    cn_bias_tot    = 'pcbias.nc' 
     1309   ln_bias_pc_app = .false.         
     1310   fb_t_asm       = 0.0 
     1311   fb_t_rlx       = 0.0 
     1312   fb_t_ofl       = 1.0 
     1313   fb_p_asm       = 1.0 
     1314   fb_p_rlx       = 1.0 
     1315   fb_p_ofl       = 0.0 
     1316   eft_rlx        = 365.0 
     1317   eft_asm        = 365.0 
     1318   t_rlx_upd      = 0.1 
     1319   t_asm_upd      = 0.1 
     1320   nn_lat_ramp    = 0           
    13121321   bias_time_unit_asm = 86400.0 
    1313    nn_lat_ramp    = 0 
    1314 / 
     1322   bias_time_unit_rlx = 1.0 
     1323   bias_time_unit_ofl = 1.0  
     1324   cn_bias_tot    = "bias_tot.nc"  
     1325   cn_bias_asm    = "bias_asm.nc" 
     1326   cn_dir         = './'   
     1327   ln_bsyncro     = .FALSE.  
     1328   fctamp         = 1. 
     1329   rn_maxlat_bias = 23.0       
     1330   rn_minlat_bias = 10.0 
     1331   nn_bias_itwrt  = 15 
     1332   ln_itdecay     = .FALSE. 
     1333/ 
  • branches/UKMO/dev_r5518_pcbias/NEMOGCM/NEMO/OPA_SRC/ASM/bias.F90

    r6300 r6328  
    113113      &   bias_wrt 
    114114 
    115 #if defined key_bias 
    116     LOGICAL, PUBLIC, PARAMETER :: lk_bias = .TRUE.   !: Logical switch for bias correction 
    117 #else 
    118     LOGICAL, PUBLIC, PARAMETER :: lk_bias = .FALSE.  !: No bias correction 
    119 #endif 
    120115  
    121116   !! * Shared variables 
     
    138133      & fb_p_ofl,             &  !: parition of bias in P for ofl bias term 
    139134      & fctamp,               &  !: amplification factor for T if inertial 
    140       & rn_maxlat,              &  !: Max lat for latitudinal ramp 
    141       & rn_minlat                  !: Min lat for latitudinal ramp 
     135      & rn_maxlat_bias,         &  !: Max lat for latitudinal ramp 
     136      & rn_minlat_bias             !: Min lat for latitudinal ramp 
    142137 
    143138   LOGICAL,  PRIVATE :: lalloc 
     
    218213         & bias_time_unit_asm, bias_time_unit_rlx, bias_time_unit_ofl,    & 
    219214         & cn_bias_tot, cn_bias_asm, cn_dir, sn_tbias_ofl, sn_sbias_ofl,  & 
    220          & ln_bsyncro, fctamp, rn_maxlat, rn_minlat, nn_bias_itwrt, ln_itdecay 
     215         & ln_bsyncro, fctamp, rn_maxlat_bias, rn_minlat_bias,            & 
     216         & nn_bias_itwrt, ln_itdecay 
    221217  
    222218 
    223219      !----------------------------------------------------------------------- 
    224       ! Read Namelist nam_bias : bias interface 
     220      ! Read Namelist : bias interface 
    225221      !----------------------------------------------------------------------- 
    226        
    227       ! Set default values 
    228       log2           = LOG( 2.0_wp ) 
    229       ln_bias        = .FALSE. 
    230       ln_bias_asm    = .FALSE. 
    231       ln_bias_rlx    = .FALSE. 
    232       ln_bias_ofl    = .FALSE. 
    233       ln_bias_ts_app = .FALSE. 
    234       ln_bias_pc_app = .FALSE. 
    235  
    236       bias_time_unit_asm = 10.*86400.0_wp ! time unit for bias term 
    237       bias_time_unit_rlx = 1.0_wp     ! same as rlx terms, i.e. seconds.  
    238       bias_time_unit_ofl = 1.0_wp     ! same as ofl terms, i.e. seconds.  
    239  
    240       eft_rlx        = 365.0_wp  !efolding time for bias estimation 
    241       eft_asm        = 365.0_wp  !efolding time for bias estimation 
    242 !      t_rlx_mem      = 1. - log2 * rdt / (eft_rlx * rday) 
    243       t_rlx_mem      = EXP( - log2 * rdt / ( eft_rlx * rday ) ) 
    244       t_rlx_upd      = 0.1_wp 
    245       t_asm_mem      = EXP( - log2 * bias_time_unit_asm / ( eft_asm * rday ) ) 
    246       t_asm_upd      = 0.1_wp 
    247       fctamp         = 1. 
    248       fb_t_rlx       = 0.0_wp 
    249       fb_t_asm       = 0.0_wp 
    250       fb_t_ofl       = 1.0_wp 
    251       fb_p_rlx       = 1.0_wp 
    252       fb_p_asm       = 1.0_wp 
    253       fb_p_ofl       = 0.0_wp 
    254       nn_lat_ramp    = 0 
    255       ln_bsyncro     = .FALSE. 
    256       ln_itdecay     = .FALSE. 
    257       rn_maxlat      = 23.0_wp 
    258       rn_minlat      = 10.0_wp 
    259        
    260       IF ( lk_asminc ) THEN 
    261          nn_bias_itwrt = nitiaufin 
    262       ELSE 
    263          nn_bias_itwrt = nitend 
    264       ENDIF 
    265  
    266  
    267       cn_bias_asm = "bias_asm.nc" 
    268       cn_bias_tot = "bias_tot.nc" 
    269       cn_dir = './'       ! directory in which the model is executed 
     222 
     223 
     224      REWIND( numnam_ref )              ! Namelist nambias in reference namelist : Bias pressure correction 
     225      READ  ( numnam_ref, nambias, IOSTAT = ios, ERR = 901) 
     226901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambias in reference namelist', lwp ) 
     227 
     228 
     229      ! Set additional default values (note that most values are set in the reference namelist) 
     230       
     231      IF ( ln_asmiau ) nn_bias_itwrt = nitiaufin 
     232       
    270233      ! ... default values (NB: frequency positive => hours, negative => months) 
    271234      !            !   file    ! frequency !  variable  ! time intep !  clim   ! 'yearly' or ! 
     
    273236      sn_tbias_ofl = FLD_N( 'tbias_ofl'    ,    -1.    ,  'tbias'     ,  .TRUE.   , .FALSE. ,   'yearly', '', '', ''  ) 
    274237      sn_sbias_ofl = FLD_N( 'sbias_ofl'    ,    -1.    ,  'sbias'     ,  .TRUE.   , .FALSE. ,   'yearly', '', '', ''  ) 
    275       lrst_bias    = .FALSE. 
    276        
    277       REWIND( numnam_ref )              ! Namelist nambias in reference namelist : Bias pressure correction 
    278       READ  ( numnam_ref, nambias, IOSTAT = ios, ERR = 901) 
    279 901   IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambias in reference namelist', lwp ) 
     238 
    280239 
    281240      REWIND( numnam_cfg )              ! Namelist nambias in configuration namelist : Bias pressure correction 
     
    290249         ln_bias        = .FALSE. 
    291250      ENDIF 
    292  
     251       
     252      ! set up decay scales 
     253      log2           = LOG( 2.0_wp ) 
    293254      t_rlx_mem      = EXP( - log2 * rdt / ( eft_rlx * rday ) ) 
    294255      t_asm_mem      = EXP( - log2 * bias_time_unit_asm/ ( eft_asm * rday ) ) 
     256       
    295257      ! Control print 
    296258      IF(lwp) THEN 
     
    498460      !latitudinal dependence of partition coeficients. Adhoc 
    499461      IF ( nn_lat_ramp == 1 ) THEN 
    500          !!!fbcoef(:,:) = SIN( rad * gphit(:,:) )**2 
    501          !!! Introduce the (also adhoc) FOAM parameterisation for latitudinal dependence. 
    502          !!! This should be added as a different namelist option later. MM. 08/2011. 
    503          lenscl_bias = ( rn_maxlat - rn_minlat )*2._wp 
    504          WHERE ( abs( gphit(:,:) ) <= rn_minlat )          
     462         ! Use the inertial ramp. 
     463         lenscl_bias = ( rn_maxlat_bias - rn_minlat_bias )*2._wp 
     464         WHERE ( abs( gphit(:,:) ) <= rn_minlat_bias )          
    505465            fbcoef(:,:) = 0._wp           
    506          ELSEWHERE ( abs( gphit(:,:) ) >= rn_maxlat )          
     466         ELSEWHERE ( abs( gphit(:,:) ) >= rn_maxlat_bias )          
    507467            fbcoef(:,:) = 1._wp                     
    508468         ELSEWHERE         
    509             fbcoef(:,:) = 1._wp - exp( -( abs( gphit(:,:) ) - rn_minlat ) & 
    510                            * ( abs( gphit(:,:) ) - rn_minlat ) / lenscl_bias )                          
     469            fbcoef(:,:) = 1._wp - exp( -( abs( gphit(:,:) ) - rn_minlat_bias ) & 
     470                           * ( abs( gphit(:,:) ) - rn_minlat_bias ) / lenscl_bias )                          
    511471         ENDWHERE  
    512472      ELSEIF ( nn_lat_ramp == 2 ) THEN    
    513473         ! Use a linear ramp consist with the geostrophic velocity balance ramp in NEMOVAR 
    514474      
    515          WHERE ( abs( gphit(:,:) ) <= rn_minlat ) 
     475         WHERE ( abs( gphit(:,:) ) <= rn_minlat_bias ) 
    516476            fbcoef(:,:) = 0._wp 
    517          ELSEWHERE ( abs( gphit(:,:) ) >= rn_maxlat )  
     477         ELSEWHERE ( abs( gphit(:,:) ) >= rn_maxlat_bias )  
    518478            fbcoef(:,:) = 1._wp 
    519479         ELSEWHERE 
    520             fbcoef(:,:) = 1._wp - ((rn_maxlat - abs( gphit(:,:)))/(rn_maxlat - rn_minlat)) 
     480            fbcoef(:,:) = 1._wp - ((rn_maxlat_bias - abs( gphit(:,:)))/(rn_maxlat_bias - rn_minlat_bias)) 
    521481         ENDWHERE 
    522482      ELSE 
     
    696656            ! if last outer loop (lk_asminc=true and ln_trainc=true). t/sbias_asm 
    697657            ! is updated, only once (end of run) taking into account units. 
    698                IF ( (kt == nn_bias_itwrt) .and. lrst_bias) THEN 
    699                  IF(lwp) WRITE(numout,*)' estimating asm bias at last timestep: ',kt 
     658               IF ( kt == nn_bias_itwrt ) THEN 
     659                 IF(lwp) WRITE(numout,*)' estimating asm bias at timestep: ',kt 
    700660                 DO jk = 1, jpkm1 
    701661                   tbias_asm_out(:,:,jk) = t_asm_mem * tbias_asm(:,:,jk)  +             & 
  • branches/UKMO/dev_r5518_pcbias/NEMOGCM/NEMO/OPA_SRC/ASM/biaspar.F90

    r6279 r6328  
    1616 
    1717   !! * Shared module variables 
    18    LOGICAL, PUBLIC :: & 
    19       & ln_bias,        & !: estimate (apply) bias arrays  
    20       & ln_bias_asm   , & !: estimate bias from assim incr 
    21       & ln_bias_rlx   , & !: estimate bias from relaxation 
    22       & ln_bias_ofl   , & !: bias estimated offline 
    23       & ln_bias_ts_app, & !: apply T and S bias  
    24       & ln_bias_pc_app, & !: apply bias through the pres crtn. 
    25       & lrst_bias         !: flag for bias restart files 
    26  
     18   LOGICAL, PUBLIC :: ln_bias        = .FALSE. !: estimate (apply) bias arrays  
     19   LOGICAL, PUBLIC :: ln_bias_asm    = .FALSE. !: estimate bias from assim incr 
     20   LOGICAL, PUBLIC :: ln_bias_rlx    = .FALSE. !: estimate bias from relaxation  
     21   LOGICAL, PUBLIC :: ln_bias_ofl    = .FALSE. !: bias estimated offline 
     22   LOGICAL, PUBLIC :: ln_bias_ts_app = .FALSE. !: estimate (apply) bias arrays  
     23   LOGICAL, PUBLIC :: ln_bias_pc_app = .FALSE. !: estimate bias from assim incr 
     24   LOGICAL, PUBLIC :: lrst_bias      = .FALSE. !: estimate bias from assim incr 
    2725 
    2826   REAL(wp), PUBLIC, DIMENSION(:,:,:), ALLOCATABLE :: & 
  • branches/UKMO/dev_r5518_pcbias/NEMOGCM/NEMO/OPA_SRC/DYN/dynhpg.F90

    r6278 r6328  
    8585      INTEGER, INTENT(in) ::   kt   ! ocean time-step index 
    8686      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdu, ztrdv 
    87       REAL(wp), DIMENSION(jpi,jpj,jpk) ::   z_rhd_st       ! for pressure correction 
    88       REAL(wp), DIMENSION(jpi,jpj)     ::   z_gru_st       ! for pressure correction 
    89       REAL(wp), DIMENSION(jpi,jpj)     ::   z_grv_st       ! for pressure correction 
     87      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   z_rhd_st  ! tmp density storage for pressure corr  
     88      REAL(wp), DIMENSION(jpi,jpj)     ::   z_gru_st  ! tmp ua trends storage for pressure corr 
     89      REAL(wp), DIMENSION(jpi,jpj)     ::   z_grv_st  ! tmp va trends storage for pressure corr 
    9090      !!---------------------------------------------------------------------- 
    9191      ! 
  • branches/UKMO/dev_r5518_pcbias/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r6278 r6328  
    121121   INTEGER ::   numout          =    6      !: logical unit for output print; Set to stdout to ensure any early 
    122122                                            !  output can be collected; do not change 
    123    INTEGER ::   numnam          =   -1      !: logical unit for namelist 
    124123   INTEGER ::   numnam_ref      =   -1      !: logical unit for reference namelist 
    125124   INTEGER ::   numnam_cfg      =   -1      !: logical unit for configuration specific namelist 
  • branches/UKMO/dev_r5518_pcbias/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r6278 r6328  
    452452      IF( lk_diadct     )   CALL dia_dct_init   ! Sections tranports 
    453453                            CALL dia_hsb_init   ! heat content, salt content and volume budgets 
    454                             CALL     trd_init   ! Mixed-layer/Vorticity/Integral constraints trend 
    455       IF (lk_bias       )   CALL     bias_init  ! Pressure correction bias 
     454                            CALL     trd_init   ! Mixed-layer/Vorticity/Integral constraints trends 
     455                            CALL     bias_init  ! Pressure correction bias 
    456456      IF( lk_diaobs     ) THEN                  ! Observation & model comparison 
    457457                            CALL dia_obs_init            ! Initialize observational data 
  • branches/UKMO/dev_r5518_pcbias/NEMOGCM/NEMO/OPA_SRC/step.F90

    r6278 r6328  
    9797      IF( ln_crs     )       CALL iom_setkt( kstp - nit000 + 1, TRIM(cxios_context)//"_crs" )   ! tell iom we are at time step kstp 
    9898 
    99       IF( lk_bias ) THEN 
    100          IF( ln_bias )          CALL bias_opn( kstp ) 
    101       ENDIF 
     99      IF( ln_bias )          CALL bias_opn( kstp ) 
    102100 
    103101      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
     
    259257      IF( lk_trabbl      )   CALL tra_bbl    ( kstp )       ! advective (and/or diffusive) bottom boundary layer scheme 
    260258      IF( ln_tradmp      )   CALL tra_dmp    ( kstp )       ! internal damping trends 
    261       IF( lk_bias  ) THEN 
    262          IF( ln_bias     )   CALL tra_bias   ( kstp ) 
    263       ENDIF 
     259      IF( ln_bias        )   CALL tra_bias   ( kstp ) 
    264260      IF( lk_bdy         )   CALL bdy_tra_dmp( kstp )       ! bdy damping trends 
    265261                             CALL tra_adv    ( kstp )       ! horizontal & vertical advection 
     
    286282               &                                           rhd, gru , grv , aru , arv , gzu , gzv , ge3ru , ge3rv ,   & 
    287283               &                                    gtui, gtvi, grui, grvi, arui, arvi, gzui, gzvi, ge3rui, ge3rvi    ) ! of t, s, rd at the last ocean level 
    288             IF( lk_bias  ) THEN 
    289                IF( ln_bias ) CALL dyn_bias( kstp ) 
    290             ENDIF 
     284            IF( ln_bias )    CALL dyn_bias( kstp ) 
    291285      ELSE                                                  ! centered hpg  (eos then time stepping) 
    292286         IF ( .NOT. lk_dynspg_ts ) THEN                     ! eos already called in time-split case 
     
    303297         IF( ln_zdfnpc   )   CALL tra_npc( kstp )                ! update after fields by non-penetrative convection 
    304298                             CALL tra_nxt( kstp )                ! tracer fields at next time step 
    305          IF( lk_bias  ) THEN 
    306             IF( ln_bias ) CALL dyn_bias( kstp ) 
    307          ENDIF 
     299         IF( ln_bias )       CALL dyn_bias( kstp ) 
    308300      ENDIF 
    309301 
     
    366358      ENDIF 
    367359      IF( lrst_oce         )   CALL rst_write    ( kstp )   ! write output ocean restart file 
    368       IF( lk_bias  ) THEN 
    369          IF( lrst_bias )       CALL bias_wrt     ( kstp ) 
    370       ENDIF 
     360      IF( lrst_bias )          CALL bias_wrt     ( kstp ) 
    371361 
    372362      !>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>>> 
Note: See TracChangeset for help on using the changeset viewer.