<p><b>laura@ucar.edu</b> 2011-04-05 12:20:15 -0600 (Tue, 05 Apr 2011)</p><p>updated modules<br>
</p><hr noshade><pre><font color="gray">Modified: branches/atmos_physics/src/core_physics/Makefile
===================================================================
--- branches/atmos_physics/src/core_physics/Makefile        2011-04-05 18:18:19 UTC (rev 779)
+++ branches/atmos_physics/src/core_physics/Makefile        2011-04-05 18:20:15 UTC (rev 780)
@@ -68,8 +68,11 @@
         ./physics_wrf/module_cu_kfeta.o
 
 module_driver_lsm.o: \
+        module_physics_constants.o         \
+        module_physics_landuse.o           \
         module_physics_lsm_noahinit.o      \
-        module_physics_vars.o              
+        module_physics_vars.o              \
+        ./physics_wrf/module_sf_noahdrv.o
 
 module_driver_pbl.o: \
         module_physics_constants.o         \
@@ -86,7 +89,8 @@
         module_physics_aquaplanet.o        \
         module_physics_constants.o         \
         module_physics_rrtmg_swinit.o      \
-        module_physics_vars.o
+        module_physics_vars.o              \
+        ./physics_wrf/module_ra_rrtmg_sw.o
 
 module_driver_sfclayer.o: \
         module_physics_aquaplanet.o        \
@@ -98,6 +102,9 @@
         module_physics_constants.o         \
         module_physics_vars.o
 
+module_physics_control.o: \
+        module_physics_utilities.o
+
 module_physics_init.o: \
         module_driver_convection_deep.o    \
         module_driver_lsm.o                \
@@ -108,6 +115,7 @@
         module_physics_landuse.o
 
 module_physics_landuse.o: \
+        module_physics_aquaplanet.o        \
         module_physics_utilities.o
 
 module_physics_lsm_noahinit.o: \
@@ -151,6 +159,7 @@
 
 module_physics_driver.o: \
         module_driver_convection_deep.o    \
+        module_driver_lsm.o                \
         module_driver_pbl.o                \
         module_driver_sfclayer.o           \
         module_physics_constants.o         \

Modified: branches/atmos_physics/src/core_physics/module_physics_control.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_control.F        2011-04-05 18:18:19 UTC (rev 779)
+++ branches/atmos_physics/src/core_physics/module_physics_control.F        2011-04-05 18:20:15 UTC (rev 780)
@@ -17,7 +17,8 @@
 
  use configure
  use grid_types
-!use module_physics_abort
+ use module_physics_constants
+ use module_physics_utilities
 
  implicit none
  private
@@ -32,6 +33,11 @@
  subroutine physics_namelist_check
 !=============================================================================================
 
+!local variables:
+ character(len=120):: errmess
+
+!---------------------------------------------------------------------------------------------
+
  write(0,*)
  write(0,*) '--- enter subroutine physics_namelist_check:'
  write(0,*) '    config_microp_scheme       = ', config_microp_scheme
@@ -49,18 +55,18 @@
            config_microp_scheme .eq. 'kessler' .or. &amp;
            config_microp_scheme .eq. 'thompson')) then
           
-    write(0,*) 'illegal value for config_microp_scheme:', config_microp_scheme
-    stop
-!   call mpas_physics_abort('illegal value for cloud microphysics scheme')
+    write(errmess,'(A,A10)') 'illegal value for config_microp_scheme:', &amp;
+          trim(config_microp_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
 !shallow convection scheme:
  if(.not. (trim(config_conv_shallow_scheme) .eq. 'off')) then
 
-    write(0,*) 'illegal value for config_conv_shallow_scheme: ', config_conv_shallow_scheme
-!   call mpas__physics_abort('illegal value for shallow convection scheme')
-    stop
+    write(errmess,'(A,A10)') 'illegal value for config_conv_shallow_scheme: ', &amp;
+          trim(config_conv_shallow_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
@@ -68,9 +74,9 @@
  if(.not. (config_conv_deep_scheme .eq. 'off' .or. &amp;
            config_conv_deep_scheme .eq. 'kain_fritsch')) then
 
-    write(0,*) 'illegal value for config_deep_conv_scheme: ', config_conv_deep_scheme
-!   call mpas_physics_abort('illegal value for deep convection scheme')
-    stop
+    write(errmess,'(A,A10)') 'illegal value for config_deep_conv_scheme: ', &amp;
+          trim(config_conv_deep_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
@@ -78,18 +84,18 @@
  if(.not. (config_pbl_scheme .eq. 'off' .or. &amp;
            config_pbl_scheme .eq. 'ysu')) then
 
-    write(0,*) 'illegal value for pbl_scheme: ', config_pbl_scheme
-!   call mpas_physics_abort('illegal value for pbl scheme')
-    stop
+    write(errmess,'(A,A10)') 'illegal value for pbl_scheme: ', &amp;
+          trim(config_pbl_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
 !diffusion scheme:
  if(.not. (config_eddy_scheme .eq. 'off')) then
  
-    write(0,*) 'illegal value for diffusion_scheme: ', config_eddy_scheme
-!   call mpas_physics_abort('illegal value for eddy scheme')
-    stop
+    write(errmess,'(A,A10)') 'illegal value for diffusion_scheme: ', &amp;
+          trim(config_eddy_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
@@ -97,9 +103,9 @@
  if(.not. (config_radt_lw_scheme .eq. 'off ' .or. &amp;
            config_radt_lw_scheme .eq. 'rrtmg_lw')) then
  
-    write(0,*) 'illegal value for radt_lw_scheme: ', config_radt_lw_scheme
-!   call mpas_physics_abort('illegal value for longwave radiation scheme')
-    stop
+    write(errmess,'(A,A10)') 'illegal value for longwave radiation scheme: ', &amp;
+          trim(config_radt_lw_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
@@ -107,33 +113,38 @@
  if(.not. (config_radt_sw_scheme .eq. 'off ' .or. &amp;
            config_radt_sw_scheme .eq. 'rrtmg_sw')) then
  
-    write(0,*) 'illegal value for radt_sw_scheme: ', config_radt_sw_scheme
-!   call mpas_physics_abort('illegal value for shortwave radiation scheme')
-    stop
+    write(errmess,'(A,A10)') 'illegal value for shortwave radiation _scheme: ', &amp;
+          trim(config_radt_sw_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
-!surface layer scheme:
+!surface-layer scheme:
  if(.not. (config_sfclayer_scheme .eq. 'off ' .or. &amp;
            config_sfclayer_scheme .eq. 'monin_obukhov')) then
  
-    write(0,*) 'illegal value for sfclayer_scheme: ', config_sfclayer_scheme
-!   call mpas_physics_abort('illegal value for surface layer scheme')
-    stop
+    write(errmess,'(A,A10)') 'illegal value for surface layer scheme: ', &amp;
+          trim(config_sfclayer_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
-!land-surface scheme:
- if(.not. (config_lsm_scheme .eq. 'off ' .or. &amp;
-           config_lsm_scheme .eq. 'noah')) then
+!land-surface scheme: note that config_sfclayer_scheme must be defined for the land-surface
+!scheme to be called:
+ if(config_lsm_scheme .ne. 'off' .and. config_sfclayer_scheme .eq. 'off') then
  
-    write(0,*) 'illegal value for lsm_scheme: ', config_lsm_scheme
-!   call mpas_physics_abort('illegal value for land surface scheme')
-    stop
+    call physics_error_fatal('land surface scheme: ' // &amp;
+                             'set config_sfclayer_scheme different than &quot;off&quot;')
+    
+ elseif(.not. (config_lsm_scheme .eq. 'off ' .or. &amp;
+               config_lsm_scheme .eq. 'noah')) then

+    write(errmess,'(A,A10)') 'illegal value for land surface scheme: ', &amp;
+          trim(config_lsm_scheme)
+    call physics_error_fatal(errmess)
 
  endif
 
-
 !checks if any physics process is called. if not, return:
  moist_physics = .true.
  
@@ -152,137 +163,130 @@
  end subroutine physics_namelist_check
 
 !=============================================================================================
- subroutine physics_registry_init(config_do_restart,mesh,diag_physics,tend_physics)
+ subroutine physics_registry_init(config_do_restart,mesh,state,diag,diag_physics,sfc_input)
 !=============================================================================================
 
 !input and output arguments:
 !---------------------------
 logical,intent(in):: config_do_restart
  type(mesh_type),intent(in):: mesh
- type(diag_physics_type),intent(inout):: diag_physics
- type(tend_physics_type),intent(inout):: tend_physics
+ type(state_type),intent(inout):: state
+ type(diag_type),intent(inout) :: diag
+ type(diag_physics_type),intent(inout) :: diag_physics
+ type(sfc_input_type),intent(inout):: sfc_input
 
 !local variables:
- integer:: k,icell
+ integer:: k,iCell,iSoil

+ real(kind=RKIND),dimension(:),pointer:: rdzw
+ real(kind=RKIND),dimension(:),pointer:: sfc_pressure
+ real(kind=RKIND),dimension(:,:),pointer:: rho,qvapor,pressure_b,pressure_p
 
+!temporary:
+ integer:: iEdg,ip,maxEdges
+
 !---------------------------------------------------------------------------------------------
 
-!initialization of non-restart variables, namely diagnostics only:

- do icell = 1, mesh % nCells
+ write(0,*) '--- enter physics_registry_init'
 
-    diag_physics % qv_col % array(icell) = 0.
-    diag_physics % qc_col % array(icell) = 0.
-    diag_physics % qr_col % array(icell) = 0.
-    diag_physics % qi_col % array(icell) = 0.
-    diag_physics % qs_col % array(icell) = 0.
-    diag_physics % qg_col % array(icell) = 0.
+ rdzw   =&gt; mesh % rdzw % array
+ rho    =&gt; state % rho % array
+ qvapor =&gt; state % scalars % array(state%index_qv,:,:)
+ pressure_p   =&gt; diag % pressure_p % array   
+ pressure_b   =&gt; diag % pressure_base % array
+ sfc_pressure =&gt; diag % surface_pressure % array
 
-    diag_physics % sr % array(icell) = 0.
+!temporary:
+ maxEdges = mesh % maxEdges
 
- enddo
-
 !initialization of restart variables, if needed:
  if(.not. config_do_restart) then
 
-!.. 1-d variables:
-    do icell = 1, mesh % nCells
-  
-       !.. cloud microphysics:
-       diag_physics % rainnc     % array(icell) = 0.
-       diag_physics % rainncv    % array(icell) = 0.
-       diag_physics % snownc     % array(icell) = 0.
-       diag_physics % snowncv    % array(icell) = 0.
-       diag_physics % graupelnc  % array(icell) = 0.
-       diag_physics % graupelncv % array(icell) = 0.
+    do iCell = 1, mesh % nCells
 
-       !.. convection:
-       diag_physics % rainc      % array(icell) = 0.
-       diag_physics % raincv     % array(icell) = 0.
-       diag_physics % nca        % array(icell) = 0.
-       diag_physics % cubot      % array(icell) = 0.
-       diag_physics % cutop      % array(icell) = 0.
+       !land-surface parameterization: initialize the thickness of the soil layers for the
+       !Noah scheme:
+       if(sfc_input % landmask % array(iCell) == 1) then  
+          sfc_input % dzs % array(1,iCell) = 0.10
+          sfc_input % dzs % array(2,iCell) = 0.30
+          sfc_input % dzs % array(3,iCell) = 0.60
+          sfc_input % dzs % array(4,iCell) = 1.00
+       endif
 
-       !.. pbl layer:
-       diag_physics % kpbl       % array(icell) = 0.
-
-       !.. surface layer:
-       diag_physics % br         % array(icell) = 0.
-       diag_physics % cd         % array(icell) = 0.
-       diag_physics % cda        % array(icell) = 0.
-       diag_physics % chs        % array(icell) = 0.
-       diag_physics % chs2       % array(icell) = 0.
-       diag_physics % cpm        % array(icell) = 0.
-       diag_physics % cqs2       % array(icell) = 0.
-       diag_physics % ck         % array(icell) = 0.
-       diag_physics % cka        % array(icell) = 0.
-       diag_physics % gz1oz0     % array(icell) = 0.
-       diag_physics % flhc       % array(icell) = 0.
-       diag_physics % flqc       % array(icell) = 0.
-       diag_physics % hfx        % array(icell) = 0.
-       diag_physics % lh         % array(icell) = 0.
-       diag_physics % mavail     % array(icell) = 0.
-       diag_physics % mol        % array(icell) = 0.
-       diag_physics % pblh       % array(icell) = 0.
-       diag_physics % psim       % array(iCell) = 0.
-       diag_physics % psih       % array(iCell) = 0.
-       diag_physics % q2         % array(icell) = 0.
-       diag_physics % qfx        % array(icell) = 0.
-       diag_physics % qgh        % array(icell) = 0.
-       diag_physics % qsfc       % array(icell) = 0.
-       diag_physics % regime     % array(icell) = 0.
-       diag_physics % rmol       % array(icell) = 0.
-       diag_physics % t2m        % array(icell) = 0.
-       diag_physics % th2m       % array(icell) = 0.
-       diag_physics % u10        % array(icell) = 0.
-       diag_physics % ust        % array(icell) = 0.
-       diag_physics % ustm       % array(icell) = 0.
-       diag_physics % v10        % array(icell) = 0.
-       diag_physics % wspd       % array(icell) = 0.
-       diag_physics % zol        % array(icell) = 0.
-       diag_physics % znt        % array(icell) = 0.
-
     enddo
 
-!2-d variables:
-
-    do icell = 1, mesh % nCells
-    do k = 1, mesh % nVertLevels
-
-       !.. cloud fraction:
-       diag_physics % cldfrac    % array(k,icell) = 0.
-
-       !.. convection:
-       diag_physics % w0avg      % array(k,icell) = 0.
-
-       tend_physics % rthcuten   % array(k,icell) = 0.
-       tend_physics % rqvcuten   % array(k,icell) = 0.
-       tend_physics % rqccuten   % array(k,icell) = 0.
-       tend_physics % rqrcuten   % array(k,icell) = 0.
-       tend_physics % rqicuten   % array(k,icell) = 0.
-       tend_physics % rqscuten   % array(k,icell) = 0.
-
-       !.. surface layer:
-       diag_physics % exch_h     % array(k,iCell) = 0.
-
-       !.. pbl:
-       tend_physics % rublten    % array(k,icell) = 0.
-       tend_physics % rvblten    % array(k,icell) = 0.
-       tend_physics % rthblten   % array(k,icell) = 0.
-       tend_physics % rqvblten   % array(k,icell) = 0.
-       tend_physics % rqcblten   % array(k,icell) = 0.
-       tend_physics % rqiblten   % array(k,icell) = 0.
-
-       !.. shortwave radiation:
-       tend_physics % rthratensw % array(k,icell) = 0.
-
-       !.. longwave radiation:
-       tend_physics % rthratenlw % array(k,icell) = 0.
-
+    ip=min(2519,mesh%nCellsSolve)
+    do iEdg = 1, maxEdges
+       write(0,*) iEdg, mesh % CellsOnCell % array(iEdg,ip)
     enddo
+    write(0,*)
+    write(0,101) sfc_input%landmask%array(ip),(sfc_input%landmask%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,101) sfc_input%ivgtyp%array(ip),(sfc_input%ivgtyp%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,101) sfc_input%isltyp%array(ip),(sfc_input%isltyp%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,*)
+    write(0,102) sfc_input%shdmin%array(ip),(sfc_input%shdmin%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%shdmax%array(ip),(sfc_input%shdmax%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%snoalb%array(ip),(sfc_input%snoalb%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%snow%array(ip),(sfc_input%snow%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%snowc%array(ip),(sfc_input%snowc%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%skintemp%array(ip),(sfc_input%skintemp%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%sst%array(ip),(sfc_input%sst%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%tmn%array(ip),(sfc_input%tmn%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%vegfra%array(ip),(sfc_input%vegfra%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%xice%array(ip),(sfc_input%xice%array(mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,*)
+    write(0,102) sfc_input%dzs%array(1,ip),(sfc_input%dzs%array(1,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%dzs%array(2,ip),(sfc_input%dzs%array(2,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%dzs%array(3,ip),(sfc_input%dzs%array(3,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%dzs%array(4,ip),(sfc_input%dzs%array(4,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,*)
+    write(0,102) sfc_input%sh2o%array(1,ip),(sfc_input%sh2o%array(1,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%sh2o%array(2,ip),(sfc_input%sh2o%array(2,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%sh2o%array(3,ip),(sfc_input%sh2o%array(3,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%sh2o%array(4,ip),(sfc_input%sh2o%array(4,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,*)
+    write(0,102) sfc_input%smois%array(1,ip),(sfc_input%smois%array(1,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%smois%array(2,ip),(sfc_input%smois%array(2,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%smois%array(3,ip),(sfc_input%smois%array(3,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%smois%array(4,ip),(sfc_input%smois%array(4,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,*)
+    write(0,102) sfc_input%tslb%array(1,ip),(sfc_input%tslb%array(1,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%tslb%array(2,ip),(sfc_input%tslb%array(2,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%tslb%array(3,ip),(sfc_input%tslb%array(3,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,102) sfc_input%tslb%array(4,ip),(sfc_input%tslb%array(4,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    write(0,*)
+    write(0,*) 'hx:'
+    do k = 11,1,-1
+       write(0,103)k,mesh%hx%array(k,ip),(mesh%hx%array(k,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
     enddo
-
+    write(0,*) 'zgrid:'
+    do k = 11,1,-1
+       write(0,103)k,mesh%zgrid%array(k,ip),(mesh%zgrid%array(k,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    enddo
+    write(0,*) 'rho:'
+    do k = 11,1,-1
+       write(0,103)k,state%rho%array(k,ip),(state%rho%array(k,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    enddo
+    write(0,*) 'theta:'
+    do k = 11,1,-1
+       write(0,103)k,state%theta%array(k,ip),(state%theta%array(k,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    enddo
+    write(0,*) 'qv:'
+    do k = 11,1,-1
+       write(0,103)k,state%scalars%array(state%index_qv,k,ip), &amp;
+                   (state%scalars%array(state%index_qv,k,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    enddo
+    write(0,*) 'w:'
+    do k = 11,1,-1
+       write(0,103)k,state%w%array(k,ip),(state%w%array(k,mesh%cellsOnCell%array(iEdg,ip)),iEdg=1,6)
+    enddo
+    
  endif
+ 101 format(10(1x,i5))
+ 102 format(10(1x,e15.8))
+ 103 format(i2,10(1x,e15.8))

+ write(0,*) '--- exit physics_registry_init'
 
  end subroutine physics_registry_init
 

Modified: branches/atmos_physics/src/core_physics/module_physics_interface_nhyd.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_interface_nhyd.F        2011-04-05 18:18:19 UTC (rev 779)
+++ branches/atmos_physics/src/core_physics/module_physics_interface_nhyd.F        2011-04-05 18:20:15 UTC (rev 780)
@@ -9,13 +9,124 @@
 
  implicit none
  private
- public:: MPAS_to_physics,           &amp;
+ public:: allocate_forall_physics,   &amp;
+          deallocate_forall_physics, &amp;
+          MPAS_to_physics,           &amp;
           microphysics_from_MPAS,    &amp;
           microphysics_to_MPAS
 
+ integer:: i,j,k
+
  contains
 
 !=============================================================================================
+ subroutine allocate_forall_physics
+!=============================================================================================
+
+ if(.not.allocated(psfc_p))  allocate(psfc_p(ims:ime,jms:jme)           )
+ if(.not.allocated(ptop_p))  allocate(ptop_p(ims:ime,jms:jme)           )
+
+ if(.not.allocated(u_p)    )  allocate(u_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(v_p)    )  allocate(v_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(zz_p)   )  allocate(zz_p(ims:ime,kms:kme,jms:jme)    )
+ if(.not.allocated(pres_p) )  allocate(pres_p(ims:ime,kms:kme,jms:jme)  )
+ if(.not.allocated(pi_p)   )  allocate(pi_p(ims:ime,kms:kme,jms:jme)    )
+ if(.not.allocated(z_p)    )  allocate(z_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(dz_p)   )  allocate(dz_p(ims:ime,kms:kme,jms:jme)    )
+ if(.not.allocated(t_p)    )  allocate(t_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(th_p)   )  allocate(th_p(ims:ime,kms:kme,jms:jme)    )
+ if(.not.allocated(al_p)   )  allocate(al_p(ims:ime,kms:kme,jms:jme)    )
+ if(.not.allocated(rho_p)  )  allocate(rho_p(ims:ime,kms:kme,jms:jme)   )
+ if(.not.allocated(rh_p)   )  allocate(rh_p(ims:ime,kms:kme,jms:jme)    )
+
+ if(.not.allocated(w_p)    )  allocate(w_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(pres2_p))  allocate(pres2_p(ims:ime,kms:kme,jms:jme) )
+ if(.not.allocated(t2_p)   )  allocate(t2_p(ims:ime,kms:kme,jms:jme)    )
+
+ if(.not.allocated(pres_hyd_p) ) allocate(pres_hyd_p(ims:ime,kms:kme,jms:jme)  )
+ if(.not.allocated(pres2_hyd_p)) allocate(pres2_hyd_p(ims:ime,kms:kme,jms:jme) )

+ do j = jms,jme
+ do i = ims,ime
+    psfc_p(i,j)   = 0.
+    ptop_p(i,j)   = 0.
+ enddo
+ enddo
+
+ do j = jms,jme
+ do k = kms,kme
+ do i = ims,ime
+    u_p(i,k,j)     = 0.
+    v_p(i,k,j)     = 0.
+    w_p(i,k,j)     = 0.
+    pres_p(i,k,j)  = 0.
+    pi_p(i,k,j)    = 0.
+    z_p(i,k,j)     = 0.
+    dz_p(i,k,j)    = 0.
+    t_p(i,k,j)     = 0.
+    th_p(i,k,j)    = 0.
+    al_p(i,k,j)    = 0.
+    rho_p(i,k,j)   = 0.
+    rh_p(i,k,j)    = 0.
+
+    w_p(i,k,j)     = 0.
+    pres2_p(i,k,j) = 0.
+    t2_p(i,k,j)    = 0.
+
+    pres_hyd_p(i,k,j)  = 0.
+    pres2_hyd_p(i,k,j) = 0.
+ enddo
+ enddo
+ enddo
+
+!allocate moist species (to be revisited!):
+ if(.not.allocated(qv_p)   ) allocate(qv_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(qc_p)   ) allocate(qc_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(qr_p)   ) allocate(qr_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(qi_p)   ) allocate(qi_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(qs_p)   ) allocate(qs_p(ims:ime,kms:kme,jms:jme)     )
+ if(.not.allocated(qg_p)   ) allocate(qg_p(ims:ime,kms:kme,jms:jme)     )
+
+ end subroutine allocate_forall_physics
+
+!=============================================================================================
+ subroutine deallocate_forall_physics
+!=============================================================================================
+
+!de-allocation of all physics arrays:
+ if(allocated(psfc_p)  ) deallocate(psfc_p  )
+ if(allocated(ptop_p)  ) deallocate(ptop_p  )
+
+ if(allocated(u_p)     ) deallocate(u_p     )
+ if(allocated(v_p)     ) deallocate(v_p     )
+ if(allocated(zz_p)    ) deallocate(zz_p    )
+ if(allocated(pres_p)  ) deallocate(pres_p  )
+ if(allocated(pi_p)    ) deallocate(pi_p    )
+ if(allocated(z_p)     ) deallocate(z_p     )
+ if(allocated(dz_p)    ) deallocate(dz_p    )
+ if(allocated(t_p)     ) deallocate(t_p     )
+ if(allocated(th_p)    ) deallocate(th_p    )
+ if(allocated(al_p)    ) deallocate(al_p    )
+ if(allocated(rho_p)   ) deallocate(rho_p   ) 
+ if(allocated(rh_p)    ) deallocate(rh_p    ) 
+
+ if(allocated(w_p)     ) deallocate(w_p     )
+ if(allocated(pres2_p) ) deallocate(pres2_p )
+ if(allocated(t2_p)    ) deallocate(t2_p    )
+
+ if(allocated(pres_hyd_p) ) deallocate(pres_hyd_p  )
+ if(allocated(pres2_hyd_p)) deallocate(pres2_hyd_p )

+ if(allocated(qv_p)    ) deallocate(qv_p    )
+ if(allocated(qc_p)    ) deallocate(qc_p    )
+ if(allocated(qr_p)    ) deallocate(qr_p    )
+ if(allocated(qi_p)    ) deallocate(qi_p    )
+ if(allocated(qs_p)    ) deallocate(qs_p    )
+ if(allocated(qg_p)    ) deallocate(qg_p    )
+
+ end subroutine deallocate_forall_physics
+
+!=============================================================================================
  subroutine MPAS_to_physics(mesh,state,diag)
 !=============================================================================================
 
@@ -28,12 +139,15 @@
  integer:: i,k,j
  real(kind=RKIND):: z0,z1,z2,w1,w2
 
+ real(kind=RKIND),dimension(:),pointer:: latCell,lonCell
  real(kind=RKIND),dimension(:),pointer  :: fzm,fzp,rdzw
  real(kind=RKIND),dimension(:,:),pointer:: zgrid
  real(kind=RKIND),dimension(:,:),pointer:: zz,exner,pressure_b,rtheta_p,rtheta_b
  real(kind=RKIND),dimension(:,:),pointer:: rho,theta,qv,pressure_p,u,v,w
  real(kind=RKIND),dimension(:,:),pointer:: qvs,rh
 
+ integer:: ip,iEdg
+
 !---------------------------------------------------------------------------------------------
 
  write(0,*)
@@ -47,6 +161,9 @@
  write(0,*) 'kts=',kts,' kte=',kte
 
 !initialization:
+ latCell   =&gt; mesh % latCell % array
+ lonCell   =&gt; mesh % lonCell % array
+
  fzm        =&gt; mesh % fzm % array
  fzp        =&gt; mesh % fzp % array
  rdzw       =&gt; mesh % rdzw % array
@@ -104,15 +221,26 @@
  enddo
  enddo
  enddo
- write(0,*)
- i=its;j=jts
- do k = kte,kts,-1
-    write(0,201) j,i,k,zz(k,i),rho_p(i,k,j),th_p(i,k,j),t_p(i,k,j)
+ do j = jts,jte
+ do i = its,ite
+    if(pres_p(i,1,j) .lt. pres_p(i,2,j)) then
+       write(0,*)
+       write(0,*) '--- subroutine MPAS_to_phys: pres:',j,i
+       write(0,*) 'latCell=', latCell(i)
+       write(0,*) 'lonCell=', lonCell(i)
+       do k = kts,kte
+          write(0,201) j,i,k,pressure_b(k,i),pressure_p(k,i),pres_p(i,k,j),zz(k,i), &amp;
+             rho_p(i,k,j),th_p(i,k,j),t_p(i,k,j),qv_p(i,k,j)
+       enddo
+       write(0,*)
+       do k = kts,kte
+          write(0,201) j,i,k,qv_p(i,k,j),qc_p(i,k,j),qr_p(i,k,j),qi_p(i,k,j),qs_p(i,k,j), &amp;
+                       qg_p(i,k,j)
+       enddo
+       write(0,*)
+       stop
+    endif
  enddo
- write(0,*)
- i=ite;j=jte
- do k = kte,kts,-1
-    write(0,201) j,i,k,zz(k,i),rho_p(i,k,j),th_p(i,k,j),t_p(i,k,j)
  enddo
 
 !interpolation of pressure and temperature from theta points to w points:
@@ -157,31 +285,34 @@
     pres2_p(i,k,j) = psfc_p(i,j)
  enddo
  enddo 
- write(0,*)
- i=its;j=jts
- write(0,*) '--- psfc_p=', psfc_p(i,j)
- do k = kte+1,kte+1
-    write(0,201) j,i,k,pres2_p(i,k,j),t2_p(i,k,j)
+ do j = jts,jte
+ do i = its,ite
+    if(pres2_p(i,1,j) .lt. pres2_p(i,2,j)) then
+       write(0,*)
+       write(0,*) '--- subroutine MPAS_to_phys: pres2:',j,i
+       do k = kts,kte+1
+          write(0,201) j,i,k,pres2_p(i,k,j)
+       enddo
+       stop
+    endif
  enddo
- do k = kte,kts,-1
-    write(0,201) j,i,k,pres2_p(i,k,j),t2_p(i,k,j),pres_p(i,k,j),t_p(i,k,j)
  enddo
- write(0,*)
- i=ite;j=jte
- write(0,*) '--- psfc_p=', psfc_p(i,j)
- do k = kte+1,kte+1
-    write(0,201) j,i,k,pres2_p(i,k,j),t2_p(i,k,j)
+
+!calculation of the hydrostatic pressure at w points:
+ do j = jts,jte
+ do i = its,ite
+    pres2_hyd_p(i,1,j) = psfc_p(i,j)
+    do k = kts+1,kte+1
+       pres2_hyd_p(i,k,j) = pres2_hyd_p(i,k-1,j) &amp;
+                          - rho_p(i,k-1,j)*(1+qv_p(i,k-1,j))*g*dz_p(i,k-1,j)
+    enddo
  enddo
- do k = kte,kts,-1
-    write(0,201) j,i,k,pres2_p(i,k,j),pres_p(i,k,j),t2_p(i,k,j),t_p(i,k,j)
- enddo 
+ enddo
 
- write(0,*) '--- end subroutine MPAS_to_phys:'
- write(0,*)
-
 !formats: 
  201 format(3i8,10(1x,e15.8))
  202 format(2i6,10(1x,e15.8))
+ 203 format(i6,10(1x,e15.8))
 
  end subroutine MPAS_to_physics
 

Modified: branches/atmos_physics/src/core_physics/module_physics_utilities.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_utilities.F        2011-04-05 18:18:19 UTC (rev 779)
+++ branches/atmos_physics/src/core_physics/module_physics_utilities.F        2011-04-05 18:20:15 UTC (rev 780)
@@ -25,31 +25,19 @@
  end subroutine physics_message
 
 !=============================================================================================
- subroutine physics_error_fatal(istat,str)
+ subroutine physics_error_fatal(str)
 !=============================================================================================
 
 !input arguments:
  character(len=*),intent(in):: str
- integer,intent(in):: istat
 
 !---------------------------------------------------------------------------------------------
 
- write(0,*) istat
  write(0,*)
- write(0,*) ( '------------------------- FATAL CALLED -------------------------')
+ write(0,*) ( '------------------------------ FATAL CALLED ------------------------------')
  write(0,*) trim(str)
-
- error: select case(istat)
-
-    case(-1)
-       write(0,*) 'reached end of file'
-    case(1:)
-       write(0,*) 'file does not exist'
-    case default
-
- end select error
+ print*, trim(str)
  stop ' MPAS core_physics abort'
- write(0,*)
  
  end subroutine physics_error_fatal
 

Modified: branches/atmos_physics/src/core_physics/module_physics_vars.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_vars.F        2011-04-05 18:18:19 UTC (rev 779)
+++ branches/atmos_physics/src/core_physics/module_physics_vars.F        2011-04-05 18:20:15 UTC (rev 780)
@@ -23,71 +23,90 @@
 !as in wrf model.
 !=============================================================================================
 
+ logical:: l_radtlw                   !controls call to longwave radiation parameterization.
+ logical:: l_radtsw                   !controls call to shortwave parameterization.
+
+
  integer,public:: ids,ide,jds,jde,kds,kde
  integer,public:: ims,ime,jms,jme,kms,kme
  integer,public:: its,ite,jts,jte,kts,kte
  integer,public:: itf,jtf,ktf
  integer,public:: n_physics,n_microp
 
- real(kind=RKIND),public:: dt_dyn
- real(kind=RKIND),public:: dt_physics
- real(kind=RKIND),public:: dt_microp
+ real(kind=RKIND),public:: dt_dyn     !time-step for dynamics
+ real(kind=RKIND),public:: dt_physics !time-step for physics.
+ real(kind=RKIND),public:: dt_microp  !time-step for cloud microphysics parameterization.
+ real(kind=RKIND),public:: dt_radtlw  !time-step for longwave radiation parameterization  [mns]
+ real(kind=RKIND),public:: dt_radtsw  !time-step for shortwave radiation parameterization [mns]
  
 !... arrays related to surface:
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
-    psfc_p,           &amp;!surface pressure                                                 [Pa].
-    ptop_p             !model-top pressure                                               [Pa].
+    psfc_p,           &amp;!surface pressure                                                  [Pa]
+    ptop_p             !model-top pressure                                                [Pa]
 
 !... arrays related to u- and v-velocities interpolated to theta points:
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    u_p,              &amp;!u-velocity interpolated to theta points                         [m/s].
-    v_p                !v-velocity interpolated to theta points                         [m/s].
+    u_p,              &amp;!u-velocity interpolated to theta points                          [m/s]
+    v_p                !v-velocity interpolated to theta points                          [m/s]
     
 !... arrays related to vertical sounding:
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
     zz_p,             &amp;!
-    pres_p,           &amp;!pressure                                                         [Pa].
-    pi_p,             &amp;!(p_phy/p0)**(r_d/cp)                                              [-].
-    z_p,              &amp;!height of layer                                                   [m].
-    dz_p,             &amp;!layer thickness                                                   [m].
-    t_p,              &amp;!temperature                                                       [K].
-    th_p,             &amp;!potential temperature                                             [K].
-    al_p,             &amp;!inverse of air density                                        [m3/kg].
-    rho_p,            &amp;!air density                                                   [kg/m3].
-    rh_p               !relative humidity                                                 [-].
+    pres_p,           &amp;!pressure                                                          [Pa]
+    pi_p,             &amp;!(p_phy/p0)**(r_d/cp)                                               [-]
+    z_p,              &amp;!height of layer                                                    [m]
+    dz_p,             &amp;!layer thickness                                                    [m]
+    t_p,              &amp;!temperature                                                        [K]
+    th_p,             &amp;!potential temperature                                              [K]
+    al_p,             &amp;!inverse of air density                                         [m3/kg]
+    rho_p,            &amp;!air density                                                    [kg/m3]
+    rh_p               !relative humidity                                                  [-]
 
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    qv_p,             &amp;!water vapor mixing ratio                                      [kg/kg].
-    qc_p,             &amp;!cloud water mixing ratio                                      [kg/kg].
-    qr_p,             &amp;!rain mixing ratio                                             [kg/kg].
-    qi_p,             &amp;!cloud ice mixing ratio                                        [kg/kg].
-    qs_p,             &amp;!snow mixing ratio                                             [kg/kg].
-    qg_p               !graupel mixing ratio                                          [kg/kg].
+    pres_hyd_p,       &amp;!hydrostatic pressure at theta points                              [Pa]
+    pres2_hyd_p        !hydrostatic pressure at w points                                  [Pa]
+
+ real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
+    qv_p,             &amp;!water vapor mixing ratio                                       [kg/kg]
+    qc_p,             &amp;!cloud water mixing ratio                                       [kg/kg]
+    qr_p,             &amp;!rain mixing ratio                                              [kg/kg]
+    qi_p,             &amp;!cloud ice mixing ratio                                         [kg/kg]
+    qs_p,             &amp;!snow mixing ratio                                              [kg/kg]
+    qg_p               !graupel mixing ratio                                           [kg/kg]
  
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    qni_p,            &amp;!number concentration for cloud ice                             [#/kg].
-    qnr_p              !number concentration for rain                                  [#/kg].
+    qni_p,            &amp;!number concentration for cloud ice                              [#/kg]
+    qnr_p              !number concentration for rain                                   [#/kg]
 
 !... arrays located at w (vertical velocity) points, or at interface between layers:
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    w_p,              &amp;!vertical velocity                                               [m/s].
-    pres2_p,          &amp;!pressure                                                        [hPa].
-    t2_p               !temperature                                                       [K].
+    w_p,              &amp;!vertical velocity                                                [m/s]
+    pres2_p,          &amp;!pressure                                                         [hPa]
+    t2_p               !temperature                                                        [K]
 
 !=============================================================================================
 !... variables and arrays related to parameterization of cloud microphysics:
+!    warm_phase: logical that determines if we want to run warm-phase cloud microphysics only.
+!          If set to false, cold-phase cloud microphysics is active. In MPAS, we always assume
+!          that the ice phase is included (except for the Kessler scheme which includes water
+!          clouds only.
+
+!    f_qv,f_qc,f_qr,f_qi,f_qs,f_qg: These logicals were initially defined in WRF to determine
+!          which kind of hydrometeors are present. Here, we assume that all six water species
+!          are present, even if their mixing ratios and number concentrations are zero.
+
 !=============================================================================================
 
  logical,parameter:: &amp;
     warm_rain=.false.  !warm-phase cloud microphysics only (used in WRF).
 
- logical:: &amp;
-    f_qv,             &amp;!
-    f_qc,             &amp;!
-    f_qr,             &amp;!
-    f_qi,             &amp;!
-    f_qs,             &amp;!
-    f_qg               !
+ logical,parameter:: &amp;
+    f_qv = .true.,    &amp;!
+    f_qc = .true.,    &amp;!
+    f_qr = .true.,    &amp;!
+    f_qi = .true.,    &amp;!
+    f_qs = .true.,    &amp;!
+    f_qg = .true.      !
 
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
     f_ice,            &amp;!fraction of cloud ice (used in WRF only).
@@ -111,9 +130,9 @@
  logical,dimension(:,:),allocatable:: &amp;
          cu_act_flag
  real(kind=RKIND),dimension(:,:),allocatable::   &amp;
-    cubot_p,          &amp;!lowest convective level                                           [-].
-    cutop_p,          &amp;!highest convective level                                          [-].
-    nca_p,            &amp;!counter for cloud relaxation time                                 [-].
+    cubot_p,          &amp;!lowest convective level                                            [-]
+    cutop_p,          &amp;!highest convective level                                           [-]
+    nca_p,            &amp;!counter for cloud relaxation time                                  [-]
     rainc_p,          &amp;!
     raincv_p,         &amp;!
     pratec_p           !
@@ -134,15 +153,15 @@
  integer,public:: n_pbl
 
  integer,dimension(:,:),allocatable:: &amp;
-    kpbl_p             !index of PBL top                                                  [-].
+    kpbl_p             !index of PBL top                                                   [-]
 
  real(kind=RKIND),public:: dt_pbl
 
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
-    hpbl_p             !PBL height                                                        [m].
+    hpbl_p             !PBL height                                                         [m]
 
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    exch_p             !exchange coefficient                                              [-].
+    exch_p             !exchange coefficient                                               [-]
 
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
     rublten_p,        &amp;!
@@ -156,7 +175,7 @@
 !... variables and arrays related to parameterization of surface layer:
 !=============================================================================================
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
-    br_p,             &amp;!bulk richardson number                                            [-].
+    br_p,             &amp;!bulk richardson number                                             [-]
     cd_p,             &amp;!
     cda_p,            &amp;!
     ck_p,             &amp;!
@@ -165,30 +184,30 @@
     chs_p,            &amp;!
     chs2_p,           &amp;!
     cqs2_p,           &amp;!
-    gz1oz0_p,         &amp;!log of z1 over z0                                                 [-].
-    flhc_p,           &amp;!exchange coefficient for heat                                     [-].
-    flqc_p,           &amp;!exchange coefficient for moisture                                 [-].
-    hfx_p,            &amp;!upward heat flux at the surface                                [W/m2].
-    lh_p,             &amp;!latent heat flux at the surface                                [W/m2].
-    mavail_p,         &amp;!surface moisture availability                                     [-].
-    mol_p,            &amp;!T* in similarity theory                                           [K].
-    pblh_p,           &amp;!PBL height                                                        [m].
-    psih_p,           &amp;!similarity theory for heat                                        [-].
-    psim_p,           &amp;!similarity theory for momentum                                    [-].
-    q2_p,             &amp;!specific humidity at 2m                                       [kg/kg].
-    qfx_p,            &amp;!upward moisture flux at the surface                         [kg/m2/s].
+    gz1oz0_p,         &amp;!log of z1 over z0                                                  [-]
+    flhc_p,           &amp;!exchange coefficient for heat                                      [-]
+    flqc_p,           &amp;!exchange coefficient for moisture                                  [-]
+    hfx_p,            &amp;!upward heat flux at the surface                                 [W/m2]
+    lh_p,             &amp;!latent heat flux at the surface                                 [W/m2]
+    mavail_p,         &amp;!surface moisture availability                                      [-]
+    mol_p,            &amp;!T* in similarity theory                                            [K]
+    pblh_p,           &amp;!PBL height                                                         [m]
+    psih_p,           &amp;!similarity theory for heat                                         [-]
+    psim_p,           &amp;!similarity theory for momentum                                     [-]
+    q2_p,             &amp;!specific humidity at 2m                                        [kg/kg]
+    qfx_p,            &amp;!upward moisture flux at the surface                          [kg/m2/s]
     qgh_p,            &amp;!
-    qsfc_p,           &amp;!specific humidity at lower boundary                           [kg/kg].
-    regime_p,         &amp;!flag indicating PBL regime (stable_p,unstable_p,etc...)           [-].
-    rmol_p,           &amp;!1 / Monin Ob length                                               [-].
-    t2m_p,            &amp;!temperature at 2m                                                 [K].
-    th2m_p,           &amp;!potential temperature at 2m                                       [K].
-    u10_p,            &amp;!u at 10 m                                                       [m/s].
-    ust_p,            &amp;!u* in similarity theory                                         [m/s].
-    ustm_p,           &amp;!u* in similarity theory without vconv                           [m/s].
-    v10_p,            &amp;!v at 10 m                                                       [m/s].
-    wspd_p,           &amp;!wind speed                                                      [m/s].
-    znt_p,            &amp;!time-varying roughness length                                     [m].
+    qsfc_p,           &amp;!specific humidity at lower boundary                            [kg/kg]
+    regime_p,         &amp;!flag indicating PBL regime (stable_p,unstable_p,etc...)            [-]
+    rmol_p,           &amp;!1 / Monin Ob length                                                [-]
+    t2m_p,            &amp;!temperature at 2m                                                  [K]
+    th2m_p,           &amp;!potential temperature at 2m                                        [K]
+    u10_p,            &amp;!u at 10 m                                                        [m/s]
+    ust_p,            &amp;!u* in similarity theory                                          [m/s]
+    ustm_p,           &amp;!u* in similarity theory without vconv                            [m/s]
+    v10_p,            &amp;!v at 10 m                                                        [m/s]
+    wspd_p,           &amp;!wind speed                                                       [m/s]
+    znt_p,            &amp;!time-varying roughness length                                      [m]
     zol_p              !
 
 !=============================================================================================
@@ -196,79 +215,130 @@
 !=============================================================================================
 
  real(kind=RKIND):: &amp;
-    dt_radtsw,        &amp;!time-step for shortwave radiation parameterization              [mns].
-    declin,           &amp;!solar declination                                                 [-].
-    solcon             !solar constant                                                [W m-2].
+    declin,           &amp;!solar declination                                                  [-]
+    solcon             !solar constant                                                 [W m-2]
 
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
-    coszr_p,          &amp;!cosine of the solar zenith angle                                  [-].
-    gsw_p,            &amp;!net shortwave flux at surface                                 [W m-2].
-    swcf_p,           &amp;!shortwave cloud forcing at top-of-atmosphere                  [W m-2].
-    swdnb_p,          &amp;!all-sky downwelling shortwave flux at bottom-of-atmosphere    [J m-2].
-    swdnbc_p,         &amp;!clear-sky downwelling shortwave flux at bottom-of-atmosphere  [J m-2].
-    swdnt_p,          &amp;!all-sky downwelling shortwave flux at top-of-atmosphere       [J m-2].
-    swdntc_p,         &amp;!clear-sky downwelling shortwave flux at top-of-atmosphere     [J m-2].
-    swupb_p,          &amp;!all-sky upwelling shortwave flux at bottom-of-atmosphere      [J m-2].
-    swupbc_p,         &amp;!clear-sky upwelling shortwave flux at bottom-of-atmosphere    [J m-2].
-    swupt_p,          &amp;!all-sky upwelling shortwave flux at top-of-atmosphere         [J m-2].
-    swuptc_p,         &amp;!clear-sky upwelling shortwave flux at top-of-atmosphere       [J m-2].
+    coszr_p,          &amp;!cosine of the solar zenith angle                                   [-]
+    gsw_p,            &amp;!net shortwave flux at surface                                  [W m-2]
+    swcf_p,           &amp;!shortwave cloud forcing at top-of-atmosphere                   [W m-2]
+    swdnb_p,          &amp;!all-sky downwelling shortwave flux at bottom-of-atmosphere     [J m-2]
+    swdnbc_p,         &amp;!clear-sky downwelling shortwave flux at bottom-of-atmosphere   [J m-2]
+    swdnt_p,          &amp;!all-sky downwelling shortwave flux at top-of-atmosphere        [J m-2]
+    swdntc_p,         &amp;!clear-sky downwelling shortwave flux at top-of-atmosphere      [J m-2]
+    swupb_p,          &amp;!all-sky upwelling shortwave flux at bottom-of-atmosphere       [J m-2]
+    swupbc_p,         &amp;!clear-sky upwelling shortwave flux at bottom-of-atmosphere     [J m-2]
+    swupt_p,          &amp;!all-sky upwelling shortwave flux at top-of-atmosphere          [J m-2]
+    swuptc_p           !clear-sky upwelling shortwave flux at top-of-atmosphere        [J m-2]
+
+ real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
     swdnflx_p,        &amp;!
     swdnflxc_p,       &amp;!
     swupflx_p,        &amp;!
     swupflxc_p         !
 
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    rthratensw_p       !uncoupled theta tendency due to shortwave radiation           [K s-1].
+    rthratensw_p       !uncoupled theta tendency due to shortwave radiation            [K s-1]
 
 !=============================================================================================
 !... variables and arrays related to parameterization of long-wave radiation:
 !=============================================================================================
 
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
-    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].
+    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]
+    olrtoa_p           !outgoing longwave radiation at top-of-the-atmosphere           [W m-2]
+
+  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
     lwdnflx_p,        &amp;!
     lwdnflxc_p,       &amp;!
     lwupflx_p,        &amp;!
-    lwupflxc_p,       &amp;!
-    olrtoa_p           !outgoing longwave radiation at top-of-the-atmosphere          [W m-2].
+    lwupflxc_p         !
 
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    rthratenlw_p       !uncoupled theta tendency due to longwave radiation           [K s-1].
+    rthratenlw_p       !uncoupled theta tendency due to longwave radiation            [K s-1]
 
 !=============================================================================================
 !.. variables and arrays related to cloudiness:
 !=============================================================================================
 
  integer,parameter:: &amp;
-    icloud= 0          !used in WRF only.
+    icloud= 1          !used in WRF only.
 
  real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
-    cldfrac_p          !cloud fraction                                                    [-].
+    cldfrac_p          !cloud fraction                                                     [-]
 
 !=============================================================================================
+!.. variables and arrays related to land-surface parameterization:
+!=============================================================================================
+
+ integer,public:: &amp;
+    num_soils          !number of soil layers                                              [-]
+ integer,dimension(:,:),allocatable:: &amp;
+    isltyp_p,         &amp;!dominant soil type category                                        [-]
+    ivgtyp_p           !dominant vegetation category                                       [-]
+
+ real(kind=RKIND),dimension(:),allocatable:: &amp;
+    dzs_p              !thickness of soil layers                                           [m]
+ real(kind=RKIND),dimension(:,:,:),allocatable:: &amp;
+    smcrel_p,         &amp;!soil moisture threshold below which transpiration starts to stress [-]
+    sh2o_p,           &amp;!unfrozen soil moisture content                   [volumetric fraction]
+    smois_p,          &amp;!soil moisture                                    [volumetric fraction]
+    tslb_p             !soil temperature                                                   [K]
+
+ real(kind=RKIND),dimension(:,:),allocatable:: &amp;
+    acsnom_p,         &amp;!accumulated melted snow                                       [kg m-2]
+    acsnow_p,         &amp;!accumulated snow                                              [kg m-2]
+    canwat_p,         &amp;!canopy water                                                  [kg m-2]
+    chklowq_p,        &amp;!surface saturation flag                                            [-]
+    grdflx_p,         &amp;!ground heat flux                                               [W m-2]
+    lai_p,            &amp;!leaf area index                                                    [-]
+    noahres_p,        &amp;!residual of the noah land-surface scheme energy budget         [W m-2]
+    potevp_p,         &amp;!potential evaporation                                          [W m-2]
+    qz0_p,            &amp;!specific humidity at znt                                     [kg kg-1]
+    rainbl_p,         &amp;!
+    rib_p,            &amp;!?
+    sfcrunoff_p,      &amp;!surface runoff                                                 [m s-1]
+    shdmin_p,         &amp;!minimum areal fractional coverage of annual green vegetation       [-]
+    shdmax_p,         &amp;!maximum areal fractional coverage of annual green vegetation       [-]
+    smstav_p,         &amp;!moisture availability                                              [-]
+    smstot_p,         &amp;!total moisture                                                [m3 m-3]
+    snopcx_p,         &amp;!snow phase change heat flux                                    [W m-2]
+    snotime_p,        &amp;!
+    snowc_p,          &amp;!snow water equivalent                                         [kg m-2]
+    snowh_p,          &amp;!physical snow depth                                                [m]
+    swdown_p,         &amp;!downward shortwave flux at the surface                         [W m-2]
+    udrunoff_p,       &amp;!sub-surface runoff                                             [m s-1]
+    tmn_p,            &amp;!soil temperature at lower boundary                                 [K]
+    vegfra_p,         &amp;!vegetation fraction                                                [-]
+    z0_p               !background roughness length                                        [m]
+
+!=============================================================================================
 !.. variables and arrays related to surface characteristics:
 !=============================================================================================
 
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
-    xlat_p,           &amp;!longitude, west is negative                                 [degrees].
-    xlon_p             !latitude, south is negative                                 [degrees].
+    xlat_p,           &amp;!longitude, west is negative                                  [degrees]
+    xlon_p             !latitude, south is negative                                  [degrees]
 
  real(kind=RKIND),dimension(:,:),allocatable:: &amp;
-    sfc_albedo_p,     &amp;!surface albedo                                                    [-].
-    sfc_emiss_p,      &amp;!land surface emissivity                                           [-].
-    snow_p,           &amp;!snow water equivalent                                        [kg m-2].
-    tsk_p,            &amp;!surface-skin temperature                                          [K].
-    xice_p,           &amp;!ice mask                                                          [-].
-    xland_p            !land mask    (1 for land; 2 for water)                            [-].
+    sfc_albedo_p,     &amp;!surface albedo                                                     [-]
+    sfc_albbck_p,     &amp;!surface background albedo                                          [-]
+    sfc_emibck_p,     &amp;!land surface background emissivity                                 [-]
+    sfc_emiss_p,      &amp;!land surface emissivity                                            [-]
+    snoalb_p,         &amp;!annual max snow albedo                                             [-]
+    snow_p,           &amp;!snow water equivalent                                         [kg m-2]
+    tsk_p,            &amp;!surface-skin temperature                                           [K]
+    xice_p,           &amp;!ice mask                                                           [-]
+    xland_p            !land mask    (1 for land; 2 for water)                             [-]
 
 !=============================================================================================
  end module module_physics_vars

</font>
</pre>