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 11672 for NEMO/branches/2019/dev_r11085_ASINTER-05_Brodeau_Advanced_Bulk/src/OCE/SBC/sbcblk_algo_coare3p6.F90 – NEMO

Ignore:
Timestamp:
2019-10-10T12:32:53+02:00 (5 years ago)
Author:
laurent
Message:

LB: "sbcblk_skin_coare.F90" now relies on "sbcdcy.F90" (modified) to know dawn/dusk time

File:
1 edited

Legend:

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

    r11666 r11672  
    8787 
    8888 
    89    SUBROUTINE turb_coare3p6( kt, zt, zu, T_s, t_zt, q_s, q_zt, U_zu, l_use_cs, l_use_wl,  & 
    90       &                      Cd, Ch, Ce, t_zu, q_zu, U_blk,                               & 
    91       &                      Cdn, Chn, Cen,                      & 
    92       &                      Qsw, rad_lw, slp, pdT_cs,                                    & ! optionals for cool-skin (and warm-layer) 
    93       &                      isecday_utc, plong, pdT_wl, Hwl )                             ! optionals for warm-layer only 
     89   SUBROUTINE turb_coare3p6( kt, zt, zu, T_s, t_zt, q_s, q_zt, U_zu, l_use_cs, l_use_wl, & 
     90      &                      Cd, Ch, Ce, t_zu, q_zu, U_blk,                              & 
     91      &                      Cdn, Chn, Cen,                                              & 
     92      &                      Qsw, rad_lw, slp, pdT_cs,                                   & ! optionals for cool-skin (and warm-layer) 
     93      &                      pdT_wl, Hwl )                                                 ! optionals for warm-layer only 
    9494      !!---------------------------------------------------------------------- 
    9595      !!                      ***  ROUTINE  turb_coare3p6  *** 
     
    123123      !! 
    124124      !!    *  q_s  : SSQ aka saturation specific humidity at temp. T_s       [kg/kg] 
    125       !!              -> doesn't need to be given a value if skin temp computed (in case l_use_skin=True) 
    126       !!              -> MUST be given the correct value if not computing skint temp. (in case l_use_skin=False) 
     125      !!              -> doesn't need to be given a value if skin temp computed (in case l_use_cs=True or l_use_wl=True) 
     126      !!              -> MUST be given the correct value if not computing skint temp. (in case l_use_cs=False or l_use_wl=False) 
    127127      !! 
    128128      !! OPTIONAL INPUT: 
     
    132132      !!    *  slp    : sea-level pressure                                    [Pa] 
    133133      !!    * pdT_cs  : SST increment "dT" for cool-skin correction           [K] 
    134       !!    * isecday_utc: 
    135       !!    *  plong  : longitude array                                       [deg.E] 
    136134      !!    * pdT_wl  : SST increment "dT" for warm-layer correction          [K] 
    137135      !!    * Hwl     : depth of warm layer                                   [m] 
     
    172170      REAL(wp), INTENT(  out), OPTIONAL, DIMENSION(jpi,jpj) ::   pdT_cs 
    173171      ! 
    174       INTEGER,  INTENT(in   ), OPTIONAL                     ::   isecday_utc ! current UTC time, counted in second since 00h of the current day 
    175       REAL(wp), INTENT(in   ), OPTIONAL, DIMENSION(jpi,jpj) ::   plong    !             [deg.E] 
    176172      REAL(wp), INTENT(  out), OPTIONAL, DIMENSION(jpi,jpj) ::   pdT_wl   !             [K] 
    177173      REAL(wp), INTENT(  out), OPTIONAL, DIMENSION(jpi,jpj) ::   Hwl      !             [m] 
     
    194190         &                pdTw,   &  ! SST increment "dT" for warm layer correction          [K] 
    195191         &                zHwl       ! depth of warm-layer [m] 
    196  
    197       ! 
    198       LOGICAL :: lreturn_z0=.FALSE., lreturn_ustar=.FALSE., lreturn_L=.FALSE., lreturn_UN10=.FALSE. 
    199       CHARACTER(len=40), PARAMETER :: crtnm = 'turb_coare3p6@sbcblk_algo_coare3p6.F90' 
    200       CHARACTER(len=128) :: cf_tmp 
    201192      !!---------------------------------------------------------------------------------- 
    202193 
    203194      IF ( kt == 1 ) CALL COARE3P6_INIT(l_use_cs, l_use_wl) ! allocation of accumulation arrays 
    204  
    205195 
    206196      l_zt_equal_zu = .FALSE. 
     
    209199 
    210200      !! Initializations for cool skin and warm layer: 
    211       IF ( l_use_cs ) THEN 
    212          IF( .NOT.(PRESENT(Qsw) .AND. PRESENT(rad_lw) .AND. PRESENT(slp)) ) THEN 
    213             PRINT *, ' * PROBLEM ('//trim(crtnm)//'): you need to provide Qsw, rad_lw & slp to use cool-skin param!' 
    214             STOP 
    215          END IF 
    216          ALLOCATE ( pdTc(jpi,jpj) ) 
    217          pdTc(:,:) = -0.25_wp  ! First guess of skin correction 
    218       END IF 
    219  
    220       IF ( l_use_wl ) THEN 
    221          IF(.NOT.(PRESENT(Qsw) .AND. PRESENT(rad_lw) .AND. PRESENT(slp) .AND. PRESENT(isecday_utc) .AND. PRESENT(plong))) THEN 
    222             PRINT *, ' * PROBLEM ('//TRIM(crtnm)//'): you need to provide Qsw, rad_lw, slp, isecday_utc & plong to use warm-layer param!' 
    223             STOP 
    224          END IF 
    225          ALLOCATE ( pdTw(jpi,jpj) ) 
    226          IF (PRESENT(Hwl)) ALLOCATE ( zHwl(jpi,jpj) ) 
    227       END IF 
    228  
    229201      IF ( l_use_cs .OR. l_use_wl ) THEN 
     202         IF( .NOT.(PRESENT(Qsw) .AND. PRESENT(rad_lw) .AND. PRESENT(slp)) ) & 
     203            & CALL ctl_stop( 'turb_coare3p6 => provide Qsw, rad_lw & slp to ', 'use cool-skin and/or warm-layer param' ) 
    230204         ALLOCATE ( zsst(jpi,jpj) ) 
    231205         zsst = T_s ! backing up the bulk SST 
    232206         IF( l_use_cs ) T_s = T_s - 0.25   ! First guess of correction 
    233207         q_s    = rdct_qsat_salt*q_sat(MAX(T_s, 200._wp), slp) ! First guess of q_s !LOLO WL too!!! 
     208      END IF 
     209      IF ( l_use_cs ) THEN 
     210         ALLOCATE ( pdTc(jpi,jpj) ) 
     211         pdTc(:,:) = -0.25_wp  ! First guess of skin correction 
     212      END IF 
     213      IF ( l_use_wl ) THEN 
     214         ALLOCATE ( pdTw(jpi,jpj) ) 
     215         IF (PRESENT(Hwl)) ALLOCATE ( zHwl(jpi,jpj) ) 
    234216      END IF 
    235217 
     
    358340            !! In WL_COARE or , Tau_ac and Qnt_ac must be updated at the final itteration step => add a flag to do this! 
    359341            IF (PRESENT(Hwl)) THEN 
    360                CALL WL_COARE( kt, Qsw, ztmp1, zeta_u, zsst, plong, isecday_utc, MOD(nb_itt,j_itt),  pdTw,  Hwl=zHwl ) 
     342               CALL WL_COARE( Qsw, ztmp1, zeta_u, zsst, MOD(nb_itt,j_itt),  pdTw,  Hwl=zHwl ) 
    361343            ELSE 
    362                CALL WL_COARE( kt, Qsw, ztmp1, zeta_u, zsst, plong, isecday_utc, MOD(nb_itt,j_itt),  pdTw ) 
     344               CALL WL_COARE( Qsw, ztmp1, zeta_u, zsst, MOD(nb_itt,j_itt),  pdTw ) 
    363345            END IF 
    364346            !! Updating T_s and q_s !!! 
Note: See TracChangeset for help on using the changeset viewer.