diff --git a/sf_sfclayrev.F b/sf_sfclayrev.F90 similarity index 93% rename from sf_sfclayrev.F rename to sf_sfclayrev.F90 index 6ca8144..023e488 100644 --- a/sf_sfclayrev.F +++ b/sf_sfclayrev.F90 @@ -1,14 +1,12 @@ !================================================================================================================= module sf_sfclayrev - use ccpp_kinds,only: kind_phys + use machine,only: kind_phys implicit none private public:: sf_sfclayrev_run, & sf_sfclayrev_init, & - sf_sfclayrev_final, & - sf_sfclayrev_timestep_init, & - sf_sfclayrev_timestep_final + sf_sfclayrev_finalize real(kind=kind_phys),parameter:: vconvc= 1. @@ -20,59 +18,9 @@ module sf_sfclayrev contains - -!================================================================================================================= - subroutine sf_sfclayrev_timestep_init(dz2d,u2d,v2d,qv2d,p2d,t2d,dz1d,u1d,v1d,qv1d,p1d,t1d, & - its,ite,kts,kte,errmsg,errflg) -!================================================================================================================= - -!--- input arguments: - integer,intent(in):: its,ite,kts,kte - - real(kind=kind_phys),intent(in),dimension(its:ite,kts:kte):: & - dz2d,u2d,v2d,qv2d,p2d,t2d - -!--- output arguments: - character(len=*),intent(out):: errmsg - integer,intent(out):: errflg - - real(kind=kind_phys),intent(out),dimension(its:ite):: & - dz1d,u1d,v1d,qv1d,p1d,t1d - -!--- local variables: - integer:: i - -!----------------------------------------------------------------------------------------------------------------- - - do i = its,ite - dz1d(i) = dz2d(i,kts) - u1d(i) = u2d(i,kts) - v1d(i) = v2d(i,kts) - qv1d(i) = qv2d(i,kts) - p1d(i) = p2d(i,kts) - t1d(i) = t2d(i,kts) - enddo - - errmsg = 'sf_sfclayrev_timestep_init OK' - errflg = 0 - - end subroutine sf_sfclayrev_timestep_init - -!================================================================================================================= - subroutine sf_sfclayrev_timestep_final(errmsg,errflg) -!================================================================================================================= - -!--- output arguments: - character(len=*),intent(out):: errmsg - integer,intent(out):: errflg - -!----------------------------------------------------------------------------------------------------------------- - - errmsg = 'sf_sfclayrev_timestep_final OK' - errflg = 0 - - end subroutine sf_sfclayrev_timestep_final - +!> \section arg_table_sf_sfclayrev_run +!! \htmlinclude sf_sfclayrev_init.html +!! !================================================================================================================= subroutine sf_sfclayrev_init(errmsg,errflg) !================================================================================================================= @@ -105,7 +53,7 @@ subroutine sf_sfclayrev_init(errmsg,errflg) end subroutine sf_sfclayrev_init !================================================================================================================= - subroutine sf_sfclayrev_final(errmsg,errflg) + subroutine sf_sfclayrev_finalize(errmsg,errflg) !================================================================================================================= !--- output arguments: @@ -114,16 +62,16 @@ subroutine sf_sfclayrev_final(errmsg,errflg) !----------------------------------------------------------------------------------------------------------------- - errmsg = 'sf_sfclayrev_final OK' + errmsg = 'sf_sfclayrev_finalize OK' errflg = 0 - end subroutine sf_sfclayrev_final + end subroutine sf_sfclayrev_finalize !================================================================================================================= subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & cp,g,rovcp,r,xlv,psfcpa,chs,chs2,cqs2, & cpm,pblh,rmol,znt,ust,mavail,zol,mol, & - regime,psim,psih,fm,fh, & + regime,psim,psim10,psih,psih2,fm,fh, & xland,hfx,qfx,tsk, & u10,v10,th2,t2,q2,flhc,flqc,qgh, & qsfc,lh,gz1oz0,wspd,br,isfflx,dx, & @@ -135,20 +83,21 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & its,ite,errmsg,errflg & ) !================================================================================================================= + implicit none !--- input arguments: integer,intent(in):: its,ite - integer,intent(in):: isfflx - integer,intent(in):: shalwater_z0 + logical,intent(in):: isfflx + logical,intent(in):: shalwater_z0 integer,intent(in),optional:: isftcflx, iz0tlnd - integer,intent(in),optional:: scm_force_flux + logical,intent(in),optional:: scm_force_flux real(kind=kind_phys),intent(in):: svp1,svp2,svp3,svpt0 - real(kind=kind_phys),intent(in):: ep1,ep2,karman,eomeg,stbolt - real(kind=kind_phys),intent(in):: P1000mb + real(kind=kind_phys),intent(in):: ep1,ep2,karman,eomeg,stbolt !WL2023: eomeg, stbolt not used + real(kind=kind_phys),intent(in):: p1000mb real(kind=kind_phys),intent(in):: cp,g,rovcp,r,xlv - real(kind=kind_phys),intent(in):: shalwater_depth + real(kind=kind_phys),intent(in):: shalwater_depth !WL2023: not used real(kind=kind_phys),intent(in),dimension(its:ite):: & mavail, & @@ -197,7 +146,9 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & wspd, & br, & psim, & + psim10, & psih, & + psih2, & fm, & fh, & znt, & @@ -235,10 +186,10 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & zqklp1, & thx, & qx, & - psih2, & - psim2, & + !psih2, & ! move to inout to work with sfc_diag + psim2, & psih10, & - psim10, & + !psim10, & ! move to inout to work with sfc_idag denomq, & denomq2, & denomt2, & @@ -320,7 +271,7 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & thvx(i)=thx(i)*tvcon scr4(i)=scr3(i)*tvcon 50 continue -! +! do 60 i=its,ite e1=svp1*exp(svp2*(tgdsa(i)-svpt0)/(tgdsa(i)-svp3)) !for land points qsfc can come from previous time step @@ -333,7 +284,7 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & cpm(i)=cp*(1.+0.8*qx(i)) 60 continue 80 continue - + !-----COMPUTE THE HEIGHT OF FULL- AND HALF-SIGMA LEVELS ABOVE GROUND ! LEVEL, AND THE LAYER THICKNESSES. @@ -823,7 +774,7 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & !-----COMPUTE THE SURFACE SENSIBLE AND LATENT HEAT FLUXES: if(present(scm_force_flux) ) then - if(scm_force_flux.eq.1) goto 350 + if(scm_force_flux) goto 350 endif do i = its,ite qfx(i)=0. @@ -831,7 +782,7 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & enddo 350 continue - if(isfflx.eq.0) goto 410 + if(.not. isfflx) goto 410 !-----OVER WATER, ALTER ROUGHNESS LENGTH (ZNT) ACCORDING TO WIND (UST). do 360 i = its,ite @@ -839,7 +790,7 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & ! znt(i)=czo*ust(i)*ust(i)/g+ozo ! PSH - formulation for depth-dependent roughness from ! ... Jimenez and Dudhia, 2018 - if(shalwater_z0 .eq. 1) then + if(shalwater_z0) then znt(i) = depth_dependent_z0(water_depth(i),znt(i),ust(i)) else !Since V3.7 (ref: EC Physics document for Cy36r1) @@ -892,7 +843,7 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & !IF(IDRY.EQ.1)GOTO 390 ! if(present(scm_force_flux)) then - if(scm_force_flux.eq.1) goto 405 + if(scm_force_flux) goto 405 endif do 370 i = its,ite @@ -900,7 +851,7 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & qfx(i)=amax1(qfx(i),0.) lh(i)=xlv*qfx(i) 370 continue - + !-----COMPUTE SURFACE HEAT FLUX: ! 390 continue @@ -942,7 +893,7 @@ subroutine sf_sfclayrev_run(ux,vx,t1d,qv1d,p1d,dz8w1d, & cqs2(i)=ust(i)*karman/denomq2(i) chs2(i)=ust(i)*karman/denomt2(i) enddo - + 410 continue !jdf @@ -963,11 +914,8 @@ end subroutine sf_sfclayrev_run !================================================================================================================= real(kind=kind_phys) function zolri(ri,z,z0) real(kind=kind_phys),intent(in):: ri,z,z0 - - integer:: iter real(kind=kind_phys):: fx1,fx2,x1,x2 - if(ri.lt.0.)then x1=-5. x2=0. @@ -978,9 +926,7 @@ real(kind=kind_phys) function zolri(ri,z,z0) fx1=zolri2(x1,ri,z,z0) fx2=zolri2(x2,ri,z,z0) - iter = 0 do while (abs(x1 - x2) > 0.01) - if (iter .eq. 10) return !check added for potential divide by zero (2019/11) if(fx1.eq.fx2)return if(abs(fx2).lt.abs(fx1))then @@ -992,7 +938,6 @@ real(kind=kind_phys) function zolri(ri,z,z0) fx2=zolri2(x2,ri,z,z0) zolri=x2 endif - iter = iter + 1 enddo return diff --git a/sf_sfclayrev.meta b/sf_sfclayrev.meta index 923d22d..74c4716 100644 --- a/sf_sfclayrev.meta +++ b/sf_sfclayrev.meta @@ -1,759 +1,585 @@ -[ccpp-arg-table] - name = sf_sfclay_timestep_init +[ccpp-table-properties] + name = sf_sfclayrev type = scheme -[dz2d] - standard_name = layer_thickness - long_name = layer thickness - units = m - dimensions = (horizontal_begin:horizontal_end,vertical_layer_dimension) - type = real | kind = kind_phys - intent = in - optional = F -[u2d] - standard_name = x_wind - long_name = x wind - units = m s-1 - dimensions = (horizontal_begin:horizontal_end,vertical_layer_dimension) - type = real | kind = kind_phys - intent = in - optional = F -[v2d] - standard_name = y_wind - long_name = y wind - units = m s-1 - dimensions = (horizontal_begin:horizontal_end,vertical_layer_dimension) - type = real | kind = kind_phys - intent = in - optional = F -[qv2d] - standard_name = water_vapor_mixing_ratio - long_name = water vapor mixing ratio - units = kg kg-1 - dimensions = (horizontal_begin:horizontal_end,vertical_layer_dimension) - type = real | kind = kind_phys - intent = in - optional = F -[p2d] - standard_name = air_pressure - long_name = air pressure - units = Pa - dimensions = (horizontal_begin:horizontal_end,vertical_layer_dimension) - type = real | kind = kind_phys - intent = in - optional = F -[t2d] - standard_name = air_temperature - long_name = air temperature - units = K - dimensions = (horizontal_begin:horizontal_end,vertical_layer_dimension) - type = real | kind = kind_phys - intent = in - optional = F -[dz1d] - standard_name = lowest_model_layer_thickness - long_name = lowest model layer thickness - units = m - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = in - optional = F -[u1d] - standard_name = x_wind_at_the_lowest_model_level - long_name = x wind at the lowest model level - units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = in - optional = F -[v1d] - standard_name = y_wind_at_the_lowest_model_level - long_name = y wind at the lowest model level - units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = in - optional = F -[qv1d] - standard_name = water_vapor_mixing_ratio_at_the_lowest_model_level - long_name = water vapor mixing ratio at the lowest model level - units = kg kg-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = in - optional = F -[p1d] - standard_name = air_pressure_at_the_lowest_model_level - long_name = air pressure at the lowest model level - units = Pa - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = in - optional = F -[t1d] - standard_name = air_temperature_at_the_lowest_model_level - long_name = layer mean air temperature at the lowest model level - units = K - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = in - optional = F -[its] - standard_name = horizontal_begin - long_name = horizontal begin - units = none - dimensions = () - type = integer - intent = in - optional = F -[ite] - standard_name = horizontal_end - long_name = horizontal end - units = none - dimensions = () - type = integer - intent = in - optional = F -[kts] - standard_name = vertical_begin - long_name = vertical begin - units = none - dimensions = () - type = integer - intent = in - optional = F -[kte] - standard_name = vertical_end - long_name = vertical end - units = none - dimensions = () - type = integer - intent = in - optional = F -[errmsg] - standard_name = ccpp_error_message - long_name = error message for error handling in CCPP - units = 1 - dimensions = () - type = character - kind = len=* - intent = out - optional = F -[errflg] - standard_name = option_ccpp_error - long_name = option error handling in CCPP - units = flag - dimensions = () - type = integer - intent = out - optional = F -[ccpp-arg-table] - name = sf_sfclay_timestep_final - type = scheme -[errmsg] - standard_name = ccpp_error_message - long_name = error message for error handling in CCPP - units = 1 - dimensions = () - type = character - kind = len=* - intent = out - optional = F -[errflg] - standard_name = option_ccpp_error - long_name = option error handling in CCPP - units = flag - dimensions = () - type = integer - intent = out - optional = F + dependencies = ../machine.F +######################################################################## [ccpp-arg-table] - name = sf_sfclay_init + name = sf_sfclayrev_init type = scheme [errmsg] standard_name = ccpp_error_message long_name = error message for error handling in CCPP - units = 1 + units = none dimensions = () type = character kind = len=* intent = out - optional = F [errflg] - standard_name = option_ccpp_error - long_name = option error handling in CCPP - units = flag - dimensions = () - type = integer - intent = out - optional = F -[ccpp-arg-table] - name = sf_sfclay_final - type = scheme -[errmsg] - standard_name = ccpp_error_message - long_name = error message for error handling in CCPP + standard_name = ccpp_error_code + long_name = error code for error handling in CCPP units = 1 dimensions = () - type = character - kind = len=* - intent = out - optional = F -[errflg] - standard_name = option_ccpp_error - long_name = option error handling in CCPP - units = flag - dimensions = () type = integer intent = out - optional = F + +######################################################################## [ccpp-arg-table] - name = sf_sfclay_run + name = sf_sfclayrev_run type = scheme [ux] - standard_name = x_wind_at_the_lowest_model_level - long_name = x wind at the lowest model level + standard_name = x_wind_at_surface_adjacent_layer + long_name = zonal wind at lowest model layer units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [vx] - standard_name = y_wind_at_the_lowest_model_level - long_name = y wind at the lowest model level - units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + standard_name = y_wind_at_surface_adjacent_layer + long_name = meridional wind at lowest model layer + units = m s-1 + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [t1d] - standard_name = air_temperature_at_the_lowest_model_level - long_name = layer mean air temperature at the lowest model level + standard_name = air_temperature_at_surface_adjacent_layer + long_name = mean temperature at lowest model layer units = K - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [qv1d] - standard_name = water_vapor_mixing_ratio_at_the_lowest_model_level - long_name = water vapor mixing ratio at the lowest model level - units = kg kg-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + standard_name = specific_humidity_at_surface_adjacent_layer + long_name = water vapor specific humidity at lowest model layer + units = kg kg-1 + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [p1d] - standard_name = air_pressure_at_the_lowest_model_level - long_name = air pressure at the lowest model level - units = Pa - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + standard_name = air_pressure_at_surface_adjacent_layer + long_name = mean pressure at lowest model layer + units = Pa + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [dz8w1d] - standard_name = lowest_model_layer_thickness - long_name = lowest model layer thickness + standard_name = height_above_ground_at_lowest_model_layer + long_name = height above ground at 1st model layer units = m - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [cp] standard_name = specific_heat_of_dry_air_at_constant_pressure long_name = specific heat of dry air at constant pressure units = J kg-1 K-1 dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [g] standard_name = gravitational_acceleration long_name = gravitational acceleration units = m s-2 dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [rovcp] - standard_name = r_over_cp - long_name = r over cp - units = none + standard_name = ratio_of_gas_constant_dry_air_to_specific_heat_of_dry_air_at_constant_pressure + long_name = (rd/cp) + units = none dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [r] - standard_name = gas_constant_for_dry_air + standard_name = gas_constant_of_dry_air long_name = ideal gas constant for dry air units = J kg-1 K-1 dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [xlv] standard_name = latent_heat_of_vaporization_of_water_at_0C long_name = latent heat of vaporization of water at 0C units = J kg-1 dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [psfcpa] standard_name = surface_air_pressure long_name = surface air pressure units = Pa - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [chs] - standard_name = exchange_coefficient_for_heat + standard_name = surface_exchange_coefficient_for_heat_at_0m long_name = exchange coefficient for heat units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [chs2] standard_name = surface_exchange_coefficient_for_heat_at_2m long_name = exchange coefficient for heat at 2 meters units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [cqs2] standard_name = surface_exchange_coefficient_for_moisture_at_2m long_name = exchange coefficient for moisture at 2 meters units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [cpm] standard_name = heat_capacity_at_constant_pressure_for_moist_air long_name = heat capacity at constant pressure for moist air units = J kg-1 K-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [pblh] - standard_name = planetary_boundary_layer_thickness + standard_name = atmosphere_boundary_layer_thickness long_name = planetary boundary layer thickness units = m - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [rmol] standard_name = reciprocal_of_obukhov_length long_name = one over obukhov length units = m-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = out - optional = F [znt] - standard_name = surface_roughness_length - long_name = surface roughness length + standard_name = surface_roughness_length_in_m + long_name = surface roughness length in meters units = m - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = inout - optional = F [ust] - standard_name = surface_frictional_velocity + standard_name = surface_friction_velocity long_name = surface frictional velocity units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = inout - optional = F [mavail] standard_name = surface_moisture_availability long_name = surface moisture availability - units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + units = frac + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [zol] - standard_name = surface_stability_parameter + standard_name = ratio_of_height_to_monin_obukhov_length long_name = monin-obukhov surface stability parameter units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [mol] - standard_name = temperature scale + standard_name = surface_temperature_scale long_name = temperature scale units = K - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = inout - optional = F [regime] standard_name = pbl_regime_categories long_name = pbl regime categories units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [psim] standard_name = Monin_Obukhov_similarity_function_for_momentum long_name = Monin-Obukhov similarity function for momentum units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout +[psim10] + standard_name = Monin_Obukhov_similarity_function_for_momentum_at_10m + long_name = Monin-Obukhov similarity function for momentum at 10m + units = none + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [psih] standard_name = Monin_Obukhov_similarity_function_for_heat long_name = Monin-Obukhov similarity function for heat units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout +[psih2] + standard_name = Monin_Obukhov_similarity_function_for_heat_at_2m + long_name = Monin-Obukhov similarity function for heat at 2m + units = none + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [fm] - standard_name = Monin_Obukhov_similarity_function_for_momentum + standard_name = Monin_Obukhov_similarity_parameter_for_momentum long_name = Monin-Obukhov similarity parameter for momentum units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [fh] - standard_name = Monin_Obukhov_similarity_function_for_heat + standard_name = Monin_Obukhov_similarity_parameter_for_heat long_name = Monin-Obukhov similarity parameter for heat units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [xland] - standard_name = land_sea_mask - long_name = land sea mask - units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + standard_name = sea_land_ice_mask_mmm + long_name = sea/land/ice mask mmm + units = flag + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [hfx] - standard_name = surface_sensible_heat_flux - long_name = surface sensible heat flux + standard_name = kinematic_surface_upward_sensible_heat_flux + long_name = kinematic surface upward sensible heat flux units = W m-2 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = inout - optional = F [qfx] - standard_name = surface_latent_heat_flux - long_name = surface latent heat flux + standard_name = kinematic_surface_upward_latent_heat_flux + long_name = kinematic surface upward latent heat flux units = W m-2 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = inout - optional = F [tsk] standard_name = surface_skin_temperature long_name = surface skin temperature units = K - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [u10] standard_name = x_wind_at_10m long_name = x wind at 10m units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = out - optional = F [v10] standard_name = y_wind_at_10m long_name = y wind at 10m units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = out - optional = F [th2] - standard_name = potential_temperature_at_2m + standard_name = air_potential_temperature_at_2m long_name = 2 meter potential temperature units = K - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = out - optional = F [t2] - standard_name = temperature_at_2m + standard_name = air_temperature_at_2m long_name = 2 meter temperature units = K - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = out - optional = F [q2] - standard_name = water_vapor_mixing_ratio_at_2m - long_name = 2 meter water vapor mixing ratio + standard_name = specific_humidity_at_2m + long_name = 2 meter specific humidity units = kg kg-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = out - optional = F [flhc] standard_name = surface_exchange_coefficient_for_heat long_name = surface exchange coefficient for heat multiplied by cp and density units = W m-2 K-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [flqc] standard_name = surface_exchange_coefficient_for_moisture long_name = surface exchange coefficient for moisture multiplied by moisture availability and density units = kg m-2 s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [qgh] standard_name = saturation_mixing_ratio_at_lowest_model_level long_name = saturation water vapor mixing ratio at lowest model level units = kg kg-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [qsfc] - standard_name = saturation_mixing_ratio_at_surface - long_name = saturation water vapor mixing ratio at surface + standard_name = surface_specific_humidity + long_name = surface air saturation specific humidity units = kg kg-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = inout - optional = F [lh] - standard_name = surface_latent_heat_flux + standard_name = surface_upward_latent_heat_flux long_name = latent heat flux at the surface (pos = up) units = W m-2 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = out - optional = F [gz1oz0] standard_name = log_of_z_over_roughness_length long_name = log of z over z0, where z0 is roughness length units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [wspd] standard_name = wind_speed_at_lowest_model_layer long_name = wind speed at lowest model layer units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real intent = out - optional = F [br] - standard_name = bulk_richardson_number_in_surface_layer - long_name = bulk richardson number in surface layer - units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = out - optional = F + standard_name = bulk_richardson_number_at_lowest_model_level + long_name = bulk Richardson number at the surface + units = none + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = inout [isfflx] - standard_name = option_surface_heat_and_moisture_fluxes - long_name = option surface heat and moisture fluxes - units = flag + standard_name = flag_to_compute_surface_heat_and_moisture_fluxes + long_name = flag to compute surface heat and moisture fluxes + units = flag dimensions = () - type = integer + type = logical intent = in - optional = F [dx] - standard_name = cell_size - long_name = size of the grid cell + standard_name = characteristic_grid_lengthscale + long_name = size of the grid cell units = m - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [svp1] - standard_name = saturation_vapor_pressure_constant + standard_name = saturation_vapor_pressure_constant_1 long_name = constant for saturation vapor pressure calculation units = k Pa dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [svp2] - standard_name = saturation_vapor_pressure_constant + standard_name = saturation_vapor_pressure_constant_2 long_name = constant for saturation vapor pressure calculation units = none dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [svp3] - standard_name = saturation_vapor_pressure_constant + standard_name = saturation_vapor_pressure_constant_3 long_name = constant for saturation vapor pressure calculation units = K dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [svpt0] - standard_name = saturation_vapor_pressure_constant + standard_name = saturation_vapor_pressure_constant_0 long_name = constant for saturation vapor pressure calculation units = K dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [ep1] standard_name = ratio_of_vapor_to_dry_air_gas_constants_minus_one long_name = ratio of vapor to dry air gas constants minus one units = none dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [ep2] standard_name = ratio_of_dry_air_to_water_vapor_gas_constants long_name = ratio of dry air to water vapor gas constants units = none dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [karman] - standard_name = vonKarman_constant - long_name = vonKarman constant + standard_name = von_karman_constant + long_name = von karman constant units = none dimensions = () - type = real | kind = kind_phys + type = real intent = in - optional = F [eomeg] - standard_name = angular_velocity_of rotation - long_name = angular velocity of rotation - units = rad-1 + standard_name = angular_velocity_of_earth + long_name = angular velocity of earth + units = s-1 dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [stbolt] standard_name = stefan_boltzmann_constant - long_name = Stefan_Boltzmann constant - units = W m-2 deg-4 + long_name = Steffan-Boltzmann constant + units = W m-2 K-4 dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [p1000mb] standard_name = pressure_value_at_1000_hPa long_name = pressure value at 1000 hPa units = Pa dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [shalwater_z0] - standard_name = shalwater_z0 - longname = shallow water roughness scheme option - units = none + standard_name = flag_for_shallow_water_roughness_scheme + long_name = shallow water roughness scheme option + units = flag dimensions = () - type = integer + type = logical intent = in - optional = F [water_depth] standard_name = water_depth - long_name = + long_name = water depth units = m - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = in - optional = F [shalwater_depth] standard_name = shalwater_depth long_name = shallow water depth constant units = m dimensions = () - type = real | kind = kind_phys + type = real + kind = kind_phys intent = in - optional = F [isftcflx] - standard_name = option_computing_exchange_coefficients - long_name = option computing exchange coefficients - units = flag + standard_name = control_for_thermal_roughness_lengths_over_water + long_name = flag for thermal roughness lengths over water in mynnsfclay + units = 1 dimensions = () type = integer intent = in - optional = T [iz0tlnd] - standard_name = option_land_atmosphere_coupling_options - long_name = option land atmosphere coupling options - units = flag + standard_name = control_for_thermal_roughness_lengths_over_land + long_name = flag for thermal roughness lengths over land in mynnsfclay + units = 1 dimensions = () type = integer intent = in - optional = T [scm_force_flux] - standard_name = option_using_scm_forcing_fluxes - long_name = option using single column model forcing fluxes + standard_name = do_not_compute_surface_scalar_fluxes + long_name = flag for not computing surface scalar fluxes units = flag dimensions = () - type = integer + type = logical intent = in - optional = T [ustm] - standard_name = time_averaged_surface_frictional_velocity + standard_name = surface_friction_velocity_for_momentum long_name = time averaged surface frictional velocity units = m s-1 - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys intent = inout - optional = T [ck] - standard_name = enthalpy_exchange_coefficient_at_10m + standard_name = surface_drag_coefficient_for_heat_and_moisture_in_air_at_10m long_name = enthalpy exchange coefficient at 10 meters units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = inout - optional = T + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = out [cka] - standard_name = enthalpy_exchange_coefficient_at_lowest_model_level + standard_name = surface_drag_coefficient_for_heat_and_moisture_in_air long_name = enthalpy exchange coefficient at the lowest model level units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = inout - optional = T + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = out [cd] - standard_name = momentum_exchange_coefficient_at_10_m + standard_name = surface_drag_coefficient_for_momentum_in_air_at_10_m long_name = momentum exchange coefficient at 10 meters units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = inout - optional = T + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = out [cda] - standard_name = momentum_exchange_coefficient_at_lowest_model_level + standard_name = surface_drag_coefficient_for_momentum_in_air long_name = momentum exchange coefficient at the lowest model level units = none - dimensions = (horizontal_begin:horizontal_end) - type = real | kind = kind_phys - intent = inout - optional = T + dimensions = (horizontal_loop_extent) + type = real + kind = kind_phys + intent = out [its] standard_name = horizontal_begin long_name = horizontal begin @@ -761,7 +587,6 @@ dimensions = () type = integer intent = in - optional = F [ite] standard_name = horizontal_end long_name = horizontal end @@ -769,63 +594,38 @@ dimensions = () type = integer intent = in - optional = F [errmsg] standard_name = ccpp_error_message long_name = error message for error handling in CCPP - units = 1 + units = none dimensions = () type = character kind = len=* intent = out - optional = F [errflg] - standard_name = option_ccpp_error - long_name = option error handling in CCPP - units = flag + standard_name = ccpp_error_code + long_name = error code for error handling in CCPP + units = 1 dimensions = () type = integer intent = out - optional = F - +######################################################################## [ccpp-arg-table] - name = sf_sfclay_init + name = sf_sfclayrev_finalize type = scheme [errmsg] standard_name = ccpp_error_message long_name = error message for error handling in CCPP - units = 1 + units = none dimensions = () type = character kind = len=* intent = out - optional = F [errflg] - standard_name = option_ccpp_error - long_name = option error handling in CCPP - units = flag - dimensions = () - type = integer - intent = out - optional = F -[ccpp-arg-table] - name = sf_sfclay_finalize - type = scheme -[errmsg] - standard_name = ccpp_error_message - long_name = error message for error handling in CCPP + standard_name = ccpp_error_code + long_name = error code for error handling in CCPP units = 1 dimensions = () - type = character - kind = len=* - intent = out - optional = F -[errflg] - standard_name = option_ccpp_error - long_name = option error handling in CCPP - units = flag - dimensions = () type = integer intent = out - optional = F