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 11266 for NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src – NEMO

Ignore:
Timestamp:
2019-07-15T12:09:30+02:00 (5 years ago)
Author:
laurent
Message:

LB: CSWL param now uses NEMO time step (rdt) and previous-t value of t_skin as first guess.

Location:
NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbc_oce.F90

    r11182 r11266  
    153153   !!                     Cool-skin/Warm-layer 
    154154   !!---------------------------------------------------------------------- 
    155    REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tsk       !: sea-surface skin temperature out of the cool-skin/warm-layer parameterization [Celsius] 
     155   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tsk       !: sea-surface skin temperature (used if ln_skin==.true.)  [K] !LB 
    156156 
    157157    
  • NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk.F90

    r11217 r11266  
    346346      CALL fld_read( kt, nn_fsbc, sf )             ! input fields provided at the current time-step 
    347347      ! 
    348       !                                            ! compute the surface ocean fluxes using bulk formulea 
    349       IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce( kt, sf, sst_m, ssu_m, ssv_m ) 
     348      IF( kt == nit000 ) tsk(:,:) = sst_m(:,:)*tmask(:,:,1)  ! no previous estimate of skin temperature => using bulk SST 
     349      ! 
     350      IF( MOD( kt - 1, nn_fsbc ) == 0 )   CALL blk_oce( kt, sf, sst_m, ssu_m, ssv_m ) !  compute the surface ocean fluxes using bulk formulea 
    350351 
    351352#if defined key_cice 
     
    493494            CALL turb_coare   ( rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm,   &  ! COARE v3.0 
    494495               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce, & 
    495                &                Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1)) 
     496               &                Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1), & 
     497               &                Tsk_b=tsk(:,:) ) 
    496498 
    497499         CASE( np_ECMWF     ) 
    498500            CALL turb_ecmwf   ( rn_zqt, rn_zu, zst, ztpot, zsq, zqair, wndm,   &  ! ECMWF 
    499501               &                Cd_atm, Ch_atm, Ce_atm, t_zu, q_zu, zU_zu, cdn_oce, chn_oce, cen_oce, & 
    500                &                Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1)) 
    501  
     502               &                Qsw=qsr(:,:), rad_lw=sf(jp_qlw)%fnow(:,:,1), slp=sf(jp_slp)%fnow(:,:,1), & 
     503               &                Tsk_b=tsk(:,:) ) 
     504             
    502505         CASE DEFAULT 
    503506            CALL ctl_stop( 'STOP', 'sbc_oce: unsuported bulk formula selection for "ln_skin==.true."' ) 
     
    515518         END WHERE 
    516519 
    517          !LB: Update of tsk, the official array for skin temperature 
     520         !LB: Update of tsk, the "official" array for skin temperature 
    518521         tsk(:,:) = zst(:,:) 
    519522 
  • NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_algo_coare.F90

    r11215 r11266  
    5757      &                   Cd, Ch, Ce, t_zu, q_zu, U_blk,      & 
    5858      &                   Cdn, Chn, Cen,                      & 
    59       &                   Qsw, rad_lw, slp                   ) 
     59      &                   Qsw, rad_lw, slp, Tsk_b             ) 
    6060      !!---------------------------------------------------------------------- 
    6161      !!                      ***  ROUTINE  turb_coare  *** 
     
    8181      !! INPUT/OUTPUT: 
    8282      !! ------------- 
    83       !!    *  T_s  : SST or skin temperature                                 [K] 
     83      !!    *  T_s  : always "bulk SST" as input                              [K] 
     84      !!              -> unchanged "bulk SST" as output if CSWL not used      [K] 
     85      !!              -> skin temperature as output if CSWL used              [K] 
     86      !! 
    8487      !!    *  q_s  : SSQ aka saturation specific humidity at temp. T_s       [kg/kg] 
    8588      !!              -> doesn't need to be given a value if skin temp computed (in case l_use_skin=True) 
     
    9194      !!    *  rad_lw : downwelling longwave radiation at the surface  (>0)   [W/m^2] 
    9295      !!    *  slp    : sea-level pressure                                    [Pa] 
     96      !!    *  Tsk_b  : estimate of skin temperature at previous time-step    [K] 
    9397      !! 
    9498      !! OUTPUT : 
     
    122126      REAL(wp), INTENT(in   ), OPTIONAL, DIMENSION(jpi,jpj) ::   rad_lw   !             [W/m^2] 
    123127      REAL(wp), INTENT(in   ), OPTIONAL, DIMENSION(jpi,jpj) ::   slp      !             [Pa] 
     128      REAL(wp), INTENT(in   ), OPTIONAL, DIMENSION(jpi,jpj) ::   Tsk_b    !             [Pa] 
    124129      ! 
    125130      INTEGER :: j_itt 
     
    152157 
    153158      !! Initialization for cool skin: 
     159      zsst   = T_s    ! save the bulk SST 
    154160      IF( l_use_skin ) THEN 
    155          zsst   = T_s    ! save the bulk SST 
    156          T_s    = T_s - 0.25                      ! First guess of correction 
     161         ! First guess for skin temperature: 
     162         IF( PRESENT(Tsk_b) ) THEN 
     163            T_s = Tsk_b 
     164         ELSE 
     165            T_s = T_s - 0.25     ! sst - 0.25 
     166         END IF 
    157167         q_s    = rdct_qsat_salt*q_sat(MAX(T_s, 200._wp), slp) ! First guess of q_s 
    158168      END IF 
     
    202212      q_star = dq_zu*ztmp0 
    203213 
    204       ! What's need to be done if zt /= zu: 
     214      ! What needs to be done if zt /= zu: 
    205215      IF( .NOT. l_zt_equal_zu ) THEN 
    206216         !! First update of values at zu (or zt for wind) 
     
    275285            ztmp1 = U_blk*MAX(rho_air(t_zu, q_zu, slp), 1._wp)     ! rho*U10 
    276286            ztmp2 = T_s*T_s 
    277             ztmp1 = ztmp1 * ( Ce*rLevap*(q_zu - q_s) + Ch*rCp_dry*(t_zu - T_s) ) & ! Total turb. heat flux 
    278                &       +    (rad_lw - emiss_w*stefan*ztmp2*ztmp2)                  ! Net longwave flux 
     287            ztmp1 = ztmp1 * ( Ce*L_vap(T_s)*(q_zu - q_s) + Ch*cp_air(q_zu)*(t_zu - T_s) ) & ! Total turb. heat flux 
     288               &       +      rad_lw - emiss_w*stefan*ztmp2*ztmp2                           ! Net longwave flux 
     289            !!         => "ztmp1" is the net non-solar surface heat flux ! 
    279290            !! Updating the values of the skin temperature T_s and q_s : 
    280291            CALL CSWL_ECMWF( Qsw, ztmp1, u_star, zsst, T_s ) ! yes ECMWF, because more advanced than COARE (warm-layer added!) 
  • NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_algo_ecmwf.F90

    r11215 r11266  
    6363      &                   Cd, Ch, Ce, t_zu, q_zu, U_blk,      & 
    6464      &                   Cdn, Chn, Cen,                      & 
    65       &                   Qsw, rad_lw, slp                   ) 
     65      &                   Qsw, rad_lw, slp, Tsk_b             ) 
    6666      !!---------------------------------------------------------------------------------- 
    6767      !!                      ***  ROUTINE  turb_ecmwf  *** 
     
    8787      !! INPUT/OUTPUT: 
    8888      !! ------------- 
    89       !!    *  T_s  : SST or skin temperature                                 [K] 
     89      !!    *  T_s  : always "bulk SST" as input                              [K] 
     90      !!              -> unchanged "bulk SST" as output if CSWL not used      [K] 
     91      !!              -> skin temperature as output if CSWL used              [K] 
     92      !! 
    9093      !!    *  q_s  : SSQ aka saturation specific humidity at temp. T_s       [kg/kg] 
    9194      !!              -> doesn't need to be given a value if skin temp computed (in case l_use_skin=True) 
     
    97100      !!    *  rad_lw : downwelling longwave radiation at the surface  (>0)   [W/m^2] 
    98101      !!    *  slp    : sea-level pressure                                    [Pa] 
     102      !!    *  Tsk_b  : estimate of skin temperature at previous time-step    [K] 
    99103      !! 
    100104      !! OUTPUT : 
     
    128132      REAL(wp), INTENT(in   ), OPTIONAL, DIMENSION(jpi,jpj) ::   rad_lw   !             [W/m^2] 
    129133      REAL(wp), INTENT(in   ), OPTIONAL, DIMENSION(jpi,jpj) ::   slp      !             [Pa] 
     134      REAL(wp), INTENT(in   ), OPTIONAL, DIMENSION(jpi,jpj) ::   Tsk_b    !             [Pa] 
    130135      ! 
    131136      INTEGER :: j_itt 
     
    156161      ! 
    157162      l_zt_equal_zu = .FALSE. 
    158       IF( ABS(zu - zt) < 0.01 )   l_zt_equal_zu = .TRUE.    ! testing "zu == zt" is risky with double precision 
     163      IF( ABS(zu - zt) < 0.01_wp )   l_zt_equal_zu = .TRUE.    ! testing "zu == zt" is risky with double precision 
    159164 
    160165      !! Initialization for cool skin: 
     166      zsst   = T_s    ! save the bulk SST 
    161167      IF( l_use_skin ) THEN 
    162          zsst   = T_s    ! save the bulk SST 
    163          T_s    = T_s - 0.25                      ! First guess of correction 
     168         ! First guess for skin temperature: 
     169         IF( PRESENT(Tsk_b) ) THEN 
     170            T_s = Tsk_b 
     171         ELSE 
     172            T_s = T_s - 0.25     ! sst - 0.25 
     173         END IF 
    164174         q_s    = rdct_qsat_salt*q_sat(MAX(T_s, 200._wp), slp) ! First guess of q_s 
    165175      END IF 
     
    209219      q_star = dq_zu*ztmp0 
    210220 
    211       ! What's need to be done if zt /= zu: 
     221      ! What needs to be done if zt /= zu: 
    212222      IF( .NOT. l_zt_equal_zu ) THEN 
    213223         !! First update of values at zu (or zt for wind) 
     
    304314            ztmp1 = U_blk*MAX(rho_air(t_zu, q_zu, slp), 1._wp)     ! rho*U10 
    305315            ztmp2 = T_s*T_s 
    306             ztmp1 = ztmp1 * ( Ce*rLevap*(q_zu - q_s) + Ch*rCp_dry*(t_zu - T_s) ) & ! Total turb. heat flux 
    307                &       +    (rad_lw - emiss_w*stefan*ztmp2*ztmp2)                  ! Net longwave flux 
     316            ztmp1 = ztmp1 * ( Ce*L_vap(T_s)*(q_zu - q_s) + Ch*cp_air(q_zu)*(t_zu - T_s) ) & ! Total turb. heat flux 
     317               &       +      rad_lw - emiss_w*stefan*ztmp2*ztmp2                           ! Net longwave flux 
     318            !!         => "ztmp1" is the net non-solar surface heat flux ! 
    308319            !! Updating the values of the skin temperature T_s and q_s : 
    309320            CALL CSWL_ECMWF( Qsw, ztmp1, u_star, zsst, T_s ) 
  • NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_phy.F90

    r11209 r11266  
    219219            zqa = (1._wp + rctv0*pqa(ji,jj)) 
    220220            ! 
    221             One_on_L(ji,jj) = grav*vkarmn*(pts(ji,jj) + rctv0*ptha(ji,jj)*pqs(ji,jj)) & 
     221            ! The main concern is to know whether, the vertical turbulent flux of virtual temperature, < u' theta_v' > is estimated with: 
     222            !  a/  -u* [ theta* (1 + 0.61 q) + 0.61 theta q* ] => this is the one that seems correct! chose this one! 
     223            !                      or 
     224            !  b/  -u* [ theta*              + 0.61 theta q* ] 
     225            ! 
     226            One_on_L(ji,jj) = grav*vkarmn*( pts(ji,jj)*zqa + rctv0*ptha(ji,jj)*pqs(ji,jj) ) & 
    222227               &               / MAX( pus(ji,jj)*pus(ji,jj)*ptha(ji,jj)*zqa , 1.E-9_wp ) 
    223228            ! 
  • NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_skin.F90

    r11182 r11266  
    3434   IMPLICIT NONE 
    3535   PRIVATE 
    36     
    37    PUBLIC :: CSWL_ECMWF   ! called by sbcblk_algo_*.F90 
     36 
     37   PUBLIC :: CSWL_ECMWF   ! called by sbcblk_algo_coare.F90 and sbcblk_algo_ecmwf.F90 
    3838 
    3939   !! Cool-Skin / Warm-Layer related parameters: 
    40    REAL(wp), PARAMETER :: rdt0 = 3600.*1.5 !: time step 
     40   !LB: we use "rdt" instead !!! REAL(wp), PARAMETER :: rdt0 = 3600.*1.5 !: time step 
    4141   REAL(wp), PARAMETER :: rd0  = 3.        !: Depth scale [m], "d" in Eq.11 (Zeng & Beljaars 2005) 
    4242   REAL(wp), PARAMETER :: rNu0 = 0.5       !: Nu (exponent of temperature profile) Eq.11 
     
    162162      IF( nbi > 1 ) THEN 
    163163         !! Itterating for warm-layer solution 
    164          zdt   = rdt0/REAL(nbi) 
     164         zdt   = rdt/REAL(nbi) 
    165165         rmult = 1._wp 
    166166      ELSE 
Note: See TracChangeset for help on using the changeset viewer.