<p><b>laura@ucar.edu</b> 2011-01-14 09:02:15 -0700 (Fri, 14 Jan 2011)</p><p>updated sourcecode<br>
</p><hr noshade><pre><font color="gray">Modified: branches/atmos_physics/src/core_physics/module_driver_sfclayer.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_driver_sfclayer.F        2011-01-13 23:52:56 UTC (rev 694)
+++ branches/atmos_physics/src/core_physics/module_driver_sfclayer.F        2011-01-14 16:02:15 UTC (rev 695)
@@ -12,26 +12,26 @@
 
  implicit none
  private
- public:: sfclayer_allocate,      &amp;
-          sfclayer_deallocate,    &amp;
-          sfclayer_driver,        &amp;
-          sfclayer_init
+ public:: init_sfclayer,          &amp;
+          allocate_sfclayer,      &amp;
+          deallocate_sfclayer,    &amp;
+          sfclayer_driver
 
  integer,parameter,private:: isfflx   = 1        !=1 for surface heat and moisture fluxes.
  integer,parameter,private:: isftcflx = 0        !=0,(Charnock and Carlson-Boland).
  integer,parameter,private:: iz0tlnd  = 0        !=0,(Carlson-Boland)
 
- real,parameter,private:: xmava   = 0.3          !max. surface moisture availability (0 to 1).
- real,parameter,private:: ust_min = 0.0001       !min. u* in similarity theory.
- real,parameter,private:: zzlnd   = 0.1          !roughness length over land.
- real,parameter,private:: zzwtr   = 0.0001       !roughness lenght over water.
+ real(kind=RKIND),parameter,private:: xmava   = 0.3    !surface moisture availability (0-&gt;1).
+ real(kind=RKIND),parameter,private:: ust_min = 0.0001 !min. u* in similarity theory.
+ real(kind=RKIND),parameter,private:: zzlnd   = 0.1    !roughness length over land.
+ real(kind=RKIND),parameter,private:: zzwtr   = 0.0001 !roughness lenght over water.
 
  integer,private:: i,iCell,j
 
  contains
 
 !=============================================================================================
- subroutine sfclayer_allocate
+ subroutine allocate_sfclayer
 !=============================================================================================
 
  if(.not.allocated(br_p)     ) allocate(br_p(ims:ime,jms:jme)     )
@@ -71,10 +71,10 @@
  if(.not.allocated(zol_p)    ) allocate(zol_p(ims:ime,jms:jme)    )
  if(.not.allocated(znt_p)    ) allocate(znt_p(ims:ime,jms:jme)    )
 
- end subroutine sfclayer_allocate
+ end subroutine allocate_sfclayer
 
 !=============================================================================================
- subroutine sfclayer_deallocate
+ subroutine deallocate_sfclayer
 !=============================================================================================
 
  if(allocated(br_p)     ) deallocate(br_p     )
@@ -114,14 +114,15 @@
  if(allocated(zol_p)    ) deallocate(zol_p    )
  if(allocated(znt_p)    ) deallocate(znt_p    )
 
- end subroutine sfclayer_deallocate
+ end subroutine deallocate_sfclayer
 
 !=============================================================================================
- subroutine sfclayer_from_MPAS(diag_physics)
+ subroutine sfclayer_from_MPAS(diag_physics,sfc_physics)
 !=============================================================================================
 
 !input arguments:
  type(diag_physics_type),intent(inout):: diag_physics
+ type(sfc_physics_type) ,intent(inout):: sfc_physics
 
 !---------------------------------------------------------------------------------------------
 
@@ -161,10 +162,10 @@
     ustm_p(i,j)   = diag_physics % ustm   % array(i)
     v10_p(i,j)    = diag_physics % v10    % array(i)
     wspd_p(i,j)   = diag_physics % wspd   % array(i)
-    xland_p(i,j)  = diag_physics % xland  % array(i)       
     zol_p(i,j)    = diag_physics % zol    % array(i)
     znt_p(i,j)    = diag_physics % znt    % array(i)
 
+    xland_p(i,j)  = sfc_physics % xland  % array(i)       
  enddo
  enddo
  
@@ -215,7 +216,6 @@
     diag_physics % ustm   % array(i) = ustm_p(i,j)
     diag_physics % v10    % array(i) = v10_p(i,j)
     diag_physics % wspd   % array(i) = wspd_p(i,j)
-    diag_physics % xland  % array(i) = xland_p(i,j)       
     diag_physics % zol    % array(i) = zol_p(i,j)
     diag_physics % znt    % array(i) = znt_p(i,j)
 
@@ -225,13 +225,14 @@
  end subroutine sfclayer_to_MPAS
 
 !=============================================================================================
- subroutine sfclayer_init(mesh,diag_physics)
+ subroutine init_sfclayer(mesh,diag_physics,sfc_physics)
 !=============================================================================================
 
 !input and output arguments:
 !---------------------------
  type(mesh_type),intent(in):: mesh
  type(diag_physics_type),intent(inout):: diag_physics
+ type(sfc_physics_type) ,intent(inout):: sfc_physics
 
 !---------------------------------------------------------------------------------------------
 
@@ -239,7 +240,7 @@
  do iCell = 1, mesh % nCells
     diag_physics % ust % array(iCell) = ust_min
     
-    if(diag_physics % xland % array(iCell) .lt. 1.5) then
+    if(sfc_physics % xland % array(iCell) .lt. 1.5) then
        diag_physics % znt % array(iCell)    = zzlnd
        diag_physics % mavail % array(iCell) = xmava
     else
@@ -250,10 +251,10 @@
  enddo
  write(0,*) '    end sfclayer_initialization:'
 
- end subroutine sfclayer_init
+ end subroutine init_sfclayer
 
 !=============================================================================================
- subroutine sfclayer_driver(itimestep,mesh,diag_physics)
+ subroutine sfclayer_driver(itimestep,mesh,diag_physics,sfc_physics)
 !=============================================================================================
 
 !input and inout arguments:
@@ -261,6 +262,7 @@
  integer,intent(in):: itimestep
  type(mesh_type),intent(in):: mesh
  type(diag_physics_type),intent(inout):: diag_physics
+ type(sfc_physics_type) ,intent(inout):: sfc_physics
 
 !local variables:
 !----------------
@@ -271,7 +273,7 @@
  write(0,*) '--- enter sfclayer_driver:'
 
 !copy all MPAS arrays to rectanguler grid arrays:
- call sfclayer_from_MPAS(diag_physics)
+ call sfclayer_from_MPAS(diag_physics,sfc_physics)
  write(0,*) '--- end sfclayer_from_MPAS:'
 
  sfclayer_select: select case (trim(sfclayer_scheme))

Modified: branches/atmos_physics/src/core_physics/module_physics_control.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_control.F        2011-01-13 23:52:56 UTC (rev 694)
+++ branches/atmos_physics/src/core_physics/module_physics_control.F        2011-01-14 16:02:15 UTC (rev 695)
@@ -38,6 +38,7 @@
  write(0,*) '    config_conv_shallow_scheme = ', config_conv_shallow_scheme
  write(0,*) '    config_conv_deep_scheme    = ', config_conv_deep_scheme
  write(0,*) '    config_eddy_scheme         = ', config_eddy_scheme
+ write(0,*) '    config_lsm_scheme          = ', config_lsm_scheme
  write(0,*) '    config_pbl_scheme          = ', config_pbl_scheme
  write(0,*) '    config_radt_lw_scheme      = ', config_radt_lw_scheme
  write(0,*) '    config_radt_sw_scheme      = ', config_radt_sw_scheme
@@ -122,12 +123,24 @@
 
  endif
 
+!land-surface scheme:
+ if(.not. (config_lsm_scheme .eq. 'off ' .or. &amp;
+           config_lsm_scheme .eq. 'noah')) then

+    write(0,*) 'illegal value for lsm_scheme: ', config_lsm_scheme
+!   call mpas_physics_abort('illegal value for land surface scheme')
+    stop
+
+ endif
+
+
 !checks if any physics process is called. if not, return:
  moist_physics = .true.
  
  if(config_microp_scheme       .eq. 'off' .and. &amp;
     config_conv_shallow_scheme .eq. 'off' .and. &amp;
     config_conv_deep_scheme    .eq. 'off' .and. &amp;
+    config_lsm_scheme          .eq. 'off' .and. &amp; 
     config_pbl_scheme          .eq. 'off' .and. &amp; 
     config_eddy_scheme         .eq. 'off' .and. &amp;
     config_radt_lw_scheme      .eq. 'off' .and. &amp;

Modified: branches/atmos_physics/src/core_physics/module_physics_manager.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_manager.F        2011-01-13 23:52:56 UTC (rev 694)
+++ branches/atmos_physics/src/core_physics/module_physics_manager.F        2011-01-14 16:02:15 UTC (rev 695)
@@ -104,6 +104,9 @@
  radt_sw_scheme = trim(config_radt_sw_scheme)
  dt_radtsw = (dt_dyn * config_n_radt_sw) / 60.
 
+!land-surface scheme:
+ lsm_scheme = trim(config_lsm_scheme)
+
 !allocation of all physics arrays:
  call physics_allocate_all
 
@@ -126,16 +129,12 @@
     conv_shallow_scheme = trim(config_conv_shallow_scheme)
 
 !initialization of variables and allocation of arrays related to surface processes:
- if(config_sfclayer_scheme .ne. 'off') then
+ if(config_sfclayer_scheme .ne. 'off') &amp;
     sfclayer_scheme = trim(config_sfclayer_scheme)
-    call sfclayer_allocate
- endif
 
 !initialization of variables and allocation of arrays related to pbl processes:
- if(config_pbl_scheme .ne. 'off' .and. config_sfclayer_scheme .ne. 'off') then
+ if(config_pbl_scheme .ne. 'off' .and. config_sfclayer_scheme .ne. 'off') &amp;
     pbl_scheme = trim(config_pbl_scheme)
-    call pbl_allocate
- endif
 
  end subroutine physics_wrf_interface
 

Modified: branches/atmos_physics/src/core_physics/module_physics_rrtmg_lwinit.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_rrtmg_lwinit.F        2011-01-13 23:52:56 UTC (rev 694)
+++ branches/atmos_physics/src/core_physics/module_physics_rrtmg_lwinit.F        2011-01-14 16:02:15 UTC (rev 695)
@@ -5,7 +5,7 @@
  use dmpar
  use grid_types
  use module_physics_constants
- use module_physics_error
+ use module_physics_utilities
 
 !wrf physics
  use module_ra_rrtmg_lw

Modified: branches/atmos_physics/src/core_physics/module_physics_vars.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_vars.F        2011-01-13 23:52:56 UTC (rev 694)
+++ branches/atmos_physics/src/core_physics/module_physics_vars.F        2011-01-14 16:02:15 UTC (rev 695)
@@ -12,6 +12,7 @@
  character(len=32),public:: microp_scheme
  character(len=32),public:: conv_deep_scheme
  character(len=32),public:: conv_shallow_scheme
+ character(len=32),public:: lsm_scheme
  character(len=32),public:: pbl_scheme
  character(len=32),public:: radt_lw_scheme
  character(len=32),public:: radt_sw_scheme
@@ -88,9 +89,9 @@
     f_qs,             &amp;!
     f_qg               !
 
- real(kind=RKIND),parameter:: &amp;
-    f_ice  = 0.,      &amp;!fraction of cloud ice (used in WRF only).
-    f_rain = 0.        !fraction of rain (used in WRF only).
+ real(kind=RKIND),dimension(:,:),allocatable:: &amp;
+    f_ice,            &amp;!fraction of cloud ice (used in WRF only).
+    f_rain             !fraction of rain (used in WRF only).
 
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
     rainnc_p,         &amp;!
@@ -224,16 +225,16 @@
 !=============================================================================================
 
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
-    glw_p,            &amp;!net shortwave flux at surface                                 [W m-2].
-    lwcf_p,           &amp;!shortwave cloud forcing at top-of-atmosphere                  [W m-2].
-    lwdnb_p,          &amp;!all-sky downwelling shortwave flux at bottom-of-atmosphere    [J m-2].
-    lwdnbc_p,         &amp;!clear-sky downwelling shortwave flux at bottom-of-atmosphere  [J m-2].
-    lwdnt_p,          &amp;!all-sky downwelling shortwave flux at top-of-atmosphere       [J m-2].
-    lwdntc_p,         &amp;!clear-sky downwelling shortwave flux at top-of-atmosphere     [J m-2].
-    lwupb_p,          &amp;!all-sky upwelling shortwave flux at bottom-of-atmosphere      [J m-2].
-    lwupbc_p,         &amp;!clear-sky upwelling shortwave flux at bottom-of-atmosphere    [J m-2].
-    lwupt_p,          &amp;!all-sky upwelling shortwave flux at top-of-atmosphere         [J m-2].
-    lwuptc_p,         &amp;!clear-sky upwelling shortwave flux at top-of-atmosphere       [J m-2].
+    glw_p,            &amp;!net longwave flux at surface                                  [W m-2].
+    lwcf_p,           &amp;!longwave cloud forcing at top-of-atmosphere                   [W m-2].
+    lwdnb_p,          &amp;!all-sky downwelling longwave flux at bottom-of-atmosphere     [J m-2].
+    lwdnbc_p,         &amp;!clear-sky downwelling longwave flux at bottom-of-atmosphere   [J m-2].
+    lwdnt_p,          &amp;!all-sky downwelling longwave flux at top-of-atmosphere        [J m-2].
+    lwdntc_p,         &amp;!clear-sky downwelling longwave flux at top-of-atmosphere      [J m-2].
+    lwupb_p,          &amp;!all-sky upwelling longwave flux at bottom-of-atmosphere       [J m-2].
+    lwupbc_p,         &amp;!clear-sky upwelling longwave flux at bottom-of-atmosphere     [J m-2].
+    lwupt_p,          &amp;!all-sky upwelling longwave flux at top-of-atmosphere          [J m-2].
+    lwuptc_p,         &amp;!clear-sky upwelling longwave flux at top-of-atmosphere        [J m-2].
     lwdnflx_p,        &amp;!
     lwdnflxc_p,       &amp;!
     lwupflx_p,        &amp;!
@@ -241,7 +242,7 @@
     olrtoa_p           !outgoing longwave radiation at top-of-the-atmosphere          [W m-2].
 
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    rthratenlw_p       !uncoupled theta tendency due to shortwave radiation           [K s-1].
+    rthratenlw_p       !uncoupled theta tendency due to longwave radiation           [K s-1].
 
 !=============================================================================================
 !.. variables and arrays related to cloudiness:

</font>
</pre>