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 6389 for branches/UKMO/dev_r5518_Surge_Modelling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90 – NEMO

Ignore:
Timestamp:
2016-03-15T11:31:28+01:00 (8 years ago)
Author:
rfurner
Message:

Added surge flux formulation, and amended bottom friction coefficient

File:
1 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r5518_Surge_Modelling/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r5954 r6389  
    9191   REAL(wp) ::   rn_zqt      ! z(q,t) : height of humidity and temperature measurements 
    9292   REAL(wp) ::   rn_zu       ! z(u)   : height of wind measurements 
    93    LOGICAL  ::   ln_charnock ! logical flag for charnock wind stress in surge model(true) or not(false) 
    9493 
    9594   !! * Substitutions 
     
    152151         &                  sn_wndi, sn_wndj, sn_humi  , sn_qsr ,           & 
    153152         &                  sn_qlw , sn_tair, sn_prec  , sn_snow,           & 
    154          &                  sn_tdif, rn_zqt , rn_zu, ln_charnock  
     153         &                  sn_tdif, rn_zqt , rn_zu 
    155154      !!--------------------------------------------------------------------- 
    156155      ! 
     
    248247      INTEGER  ::   ji, jj               ! dummy loop indices 
    249248      REAL(wp) ::   zcoef_qsatw, zztmp   ! local variable 
    250       REAL(wp) ::   z_z0, z_Cd1          ! local variable 
    251       REAL(wp) ::   i                    ! local variable 
    252       REAL(wp) ::   charn_const=0.0275    ! local variable 
    253249      REAL(wp), DIMENSION(:,:), POINTER ::   zwnd_i, zwnd_j    ! wind speed components at T-point 
    254250      REAL(wp), DIMENSION(:,:), POINTER ::   zqsatw            ! specific humidity at pst 
     
    307303      ! ocean albedo assumed to be constant + modify now Qsr to include the diurnal cycle                    ! Short Wave 
    308304      zztmp = 1. - albo 
    309 #if defined key_surge 
    310       qsr(:,:)=0._wp 
    311       zqlw(:,:) = 0._wp 
    312 #else 
    313305      IF( ln_dm2dc ) THEN   ;   qsr(:,:) = zztmp * sbc_dcy( sf(jp_qsr)%fnow(:,:,1) ) * tmask(:,:,1) 
    314306      ELSE                  ;   qsr(:,:) = zztmp *          sf(jp_qsr)%fnow(:,:,1)   * tmask(:,:,1) 
     
    316308 
    317309      zqlw(:,:) = (  sf(jp_qlw)%fnow(:,:,1) - Stef * zst(:,:)*zst(:,:)*zst(:,:)*zst(:,:)  ) * tmask(:,:,1)   ! Long  Wave 
    318 #endif 
    319310      ! ----------------------------------------------------------------------------- ! 
    320311      !     II    Turbulent FLUXES                                                    ! 
    321312      ! ----------------------------------------------------------------------------- ! 
    322       IF (ln_charnock) THEN 
    323           Cd(:,:)=0.0001_wp 
    324           DO jj = 1,jpj 
    325              DO ji = 1,jpi 
    326                 z_Cd1=0._wp 
    327                 i=1 
    328                 !Iterate 
    329                 DO WHILE((abs(Cd(ji,jj)-z_Cd1))>1E-6) 
    330                 z_Cd1=Cd(ji,jj) 
    331                 z_z0=charn_const*z_Cd1*wndm(ji,jj)**2/grav 
    332                 Cd(ji,jj)=(0.41_wp/log(10._wp/z_z0))**2 
    333                 i=i+1 
    334                 ENDDO 
    335              ENDDO 
    336           ENDDO 
    337       ELSE 
    338  
    339         ! ... specific humidity at SST and IST 
    340         zqsatw(:,:) = zcoef_qsatw * EXP( -5107.4 / zst(:,:) )  
    341  
    342         ! ... NCAR Bulk formulae, computation of Cd, Ch, Ce at T-point : 
    343         CALL turb_core_2z( rn_zqt, rn_zu, zst, sf(jp_tair)%fnow, zqsatw, sf(jp_humi)%fnow, wndm,   & 
    344            &               Cd, Ch, Ce, zt_zu, zq_zu ) 
    345  
    346       ENDIF 
     313 
     314      ! ... specific humidity at SST and IST 
     315      zqsatw(:,:) = zcoef_qsatw * EXP( -5107.4 / zst(:,:) )  
     316 
     317      ! ... NCAR Bulk formulae, computation of Cd, Ch, Ce at T-point : 
     318      CALL turb_core_2z( rn_zqt, rn_zu, zst, sf(jp_tair)%fnow, zqsatw, sf(jp_humi)%fnow, wndm,   & 
     319         &               Cd, Ch, Ce, zt_zu, zq_zu ) 
    347320 
    348321      ! ... tau module, i and j component 
     
    379352      !  Turbulent fluxes over ocean 
    380353      ! ----------------------------- 
    381 #if ! defined key_surge 
    382354      IF( ABS( rn_zu - rn_zqt) < 0.01_wp ) THEN 
    383355         !! q_air and t_air are (or "are almost") given at 10m (wind reference height) 
     
    391363      ENDIF 
    392364      zqla (:,:) = Lv * zevap(:,:)                                                              ! Latent Heat 
    393 #endif 
    394365 
    395366      IF(ln_ctl) THEN 
     
    408379      ! ----------------------------------------------------------------------------- ! 
    409380      ! 
    410 #if defined key_surge 
    411       emp (:,:) = 0._wp 
    412       qns(:,:)  = 0._wp 
    413 #else 
    414381      emp (:,:) = (  zevap(:,:)                                          &   ! mass flux (evap. - precip.) 
    415382         &         - sf(jp_prec)%fnow(:,:,1) * rn_pfac  ) * tmask(:,:,1) 
     
    422389         &     + sf(jp_snow)%fnow(:,:,1) * rn_pfac                                &   ! add solid  precip heat content at min(Tair,Tsnow) 
    423390         &     * ( MIN( sf(jp_tair)%fnow(:,:,1), rt0_snow ) - rt0 ) * cpic * tmask(:,:,1) 
    424 #endif 
    425391      ! 
    426392#if defined key_lim3 
Note: See TracChangeset for help on using the changeset viewer.