<p><b>laura@ucar.edu</b> 2011-06-20 16:49:16 -0600 (Mon, 20 Jun 2011)</p><p>revised initialization<br>
</p><hr noshade><pre><font color="gray">Modified: branches/atmos_physics/src/core_physics/module_physics_rrtmg_lwinit.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_rrtmg_lwinit.F        2011-06-16 18:54:45 UTC (rev 900)
+++ branches/atmos_physics/src/core_physics/module_physics_rrtmg_lwinit.F        2011-06-20 22:49:16 UTC (rev 901)
@@ -68,7 +68,7 @@
 
 !open init file:
  if(dminfo % my_proc_id == IO_NODE) then
-    open(rrtmg_unit,file='RRTMG_LW_DATA_DBL',form='UNFORMATTED',status='OLD',iostat=istat)
+    open(rrtmg_unit,file='RRTMG_LW_DATA.DBL',form='UNFORMATTED',status='OLD',iostat=istat)
 
     if(istat /= 0) then
        write(errmess,'(A,I4)') 'module_ra_rrtmg_lw: error reading RRTMG_LW_DATA on unit', &amp;

Modified: branches/atmos_physics/src/core_physics/module_physics_rrtmg_swinit.F
===================================================================
--- branches/atmos_physics/src/core_physics/module_physics_rrtmg_swinit.F        2011-06-16 18:54:45 UTC (rev 900)
+++ branches/atmos_physics/src/core_physics/module_physics_rrtmg_swinit.F        2011-06-20 22:49:16 UTC (rev 901)
@@ -67,7 +67,7 @@
 
 !open init file:
  if(dminfo % my_proc_id == IO_NODE) then
-    open(rrtmg_unit,file='RRTMG_SW_DATA_DBL',form='UNFORMATTED',iostat=istat)
+    open(rrtmg_unit,file='RRTMG_SW_DATA.DBL',form='UNFORMATTED',iostat=istat)
 
     if(istat /= 0) then
          write(0,*) 'rrtmg_unit=',rrtmg_unit

Modified: branches/atmos_physics/src/core_physics/physics_wrf/module_mp_thompson.F
===================================================================
--- branches/atmos_physics/src/core_physics/physics_wrf/module_mp_thompson.F        2011-06-16 18:54:45 UTC (rev 900)
+++ branches/atmos_physics/src/core_physics/physics_wrf/module_mp_thompson.F        2011-06-20 22:49:16 UTC (rev 901)
@@ -34,21 +34,17 @@
 !
       MODULE module_mp_thompson
 
-!     USE module_wrf_error
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+      USE module_physics_utilities
+#else
+      USE module_wrf_error
 !     USE module_utility, ONLY: WRFU_Clock, WRFU_Alarm
 !     USE module_domain, ONLY : HISTORY_ALARM, Is_alarm_tstep
+#endif
 
       IMPLICIT NONE
 
-!LDF begin (05-13-2010): Added the capabilities to read pre-calculated
-!look-up tables to speed up initialization.
-      LOGICAL, PRIVATE:: iiwarm
-      LOGICAL, PRIVATE:: l_qr_acr_qg
-      LOGICAL, PRIVATE:: l_qr_acr_qs
-      LOGICAL, PRIVATE:: l_qi_aut_qs
-      LOGICAL, PRIVATE:: l_freezeH2O
-!LDF end.
-!     LOGICAL, PARAMETER, PRIVATE:: iiwarm = .false.
+      LOGICAL, PARAMETER, PRIVATE:: iiwarm = .false.
       INTEGER, PARAMETER, PRIVATE:: IFDRY = 0
       REAL, PARAMETER, PRIVATE:: T_0 = 273.15
       REAL, PARAMETER, PRIVATE:: PI = 3.1415926536
@@ -336,9 +332,11 @@
       INTEGER:: i, j, k, m, n
       LOGICAL:: micro_init
 
-!LDF:
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+      INTEGER,PARAMETER:: open_OK = 0
+      INTEGER:: istat
       INTEGER:: ig1,ig,ir1,ir
-!LDF end.
+#endif
 
 !..Allocate space for lookup tables (J. Michalakes 2009Jun08).
       micro_init = .FALSE.
@@ -684,13 +682,15 @@
          enddo
       enddo
 
-!     CALL wrf_debug(150, 'CREATING MICROPHYSICS LOOKUP TABLES ... ')
-!     WRITE (wrf_err_message, '(a, f5.2, a, f5.2, a, f5.2, a, f5.2)') &amp;
-!         ' using: mu_c=',mu_c,' mu_i=',mu_i,' mu_r=',mu_r,' mu_g=',mu_g
-!     CALL wrf_debug(150, wrf_err_message)
+#if ! defined(non_hydrostatic_core) || defined(hydrostatic_core)
+      CALL wrf_debug(150, 'CREATING MICROPHYSICS LOOKUP TABLES ... ')
+      WRITE (wrf_err_message, '(a, f5.2, a, f5.2, a, f5.2, a, f5.2)') &amp;
+          ' using: mu_c=',mu_c,' mu_i=',mu_i,' mu_r=',mu_r,' mu_g=',mu_g
+      CALL wrf_debug(150, wrf_err_message)
 
 !..Collision efficiency between rain/snow and cloud water.
-!     CALL wrf_debug(200, '  creating qc collision eff tables')
+      CALL wrf_debug(200, '  creating qc collision eff tables')
+#endif
       call table_Efrw
       call table_Efsw
 
@@ -701,26 +701,15 @@
 !..Initialize various constants for computing radar reflectivity.
 !     call radar_init
 
-!LDF begin (05-13-2010): read pre-calculated look-up tables.
-      iiwarm = .false.
-      l_qr_acr_qg = .false.
-      l_qr_acr_qs = .false.
-      l_qi_aut_qs = .false.
-      l_freezeH2O = .false.
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+!MPAS specific (Laura D. Fowler): read pre-calculated look-up tables.
 
-      inquire(file='./LOOKUP_TABLES/table_qr_acr_qg.dat',exist=l_qr_acr_qg)
-      inquire(file='./LOOKUP_TABLES/table_qr_acr_qs.dat',exist=l_qr_acr_qs)
-      inquire(file='./LOOKUP_TABLES/table_qi_aut_qs.dat',exist=l_qi_aut_qs)
-      inquire(file='./LOOKUP_TABLES/table_freezeH2O.dat',exist=l_freezeH2O)
-
-      IF(l_qr_acr_qg .AND. l_qr_acr_qs .AND. l_qi_aut_qs .AND. &amp;
-         l_freezeH2O) iiwarm = .true.

-      if(iiwarm) then
-         write(0,*) '    begin read pre-calculated look-up tables'
 !..Rain collecting graupel &amp; graupel collecting rain.
-         open(unit=11,file='./LOOKUP_TABLES/table_qr_acr_qg.dat', &amp;
-              form='unformatted',status='old',action='read')
+         open(unit=11,file='MP_THOMPSON_QRacrQG.DBL',form='UNFORMATTED',status='OLD',action='READ', &amp;
+              iostat = istat)
+         if(istat /= open_OK) &amp;
+            call physics_error_fatal('subroutine thompson_init: ' // &amp;
+                                     'failure opening MP_THOMPSON_QRacrQG.DBL')
          read(11) tcg_racg
          read(11) tmr_racg
          read(11) tcr_gacr
@@ -728,60 +717,26 @@
          read(11) tnr_racg
          read(11) tnr_gacr
          close(unit=11)
-         write(0,*) '       end read table_qr_acr_qg.dat'
-         write(0,*)
-         write(0,*) '--- end subroutine qr_acr_qg:'
+         write(0,*) '--- end read MP_THOMPSON_QRacrQG.DBL'
          write(0,*) 'max tcg_racg =',maxval(tcg_racg)
          write(0,*) 'min tcg_racg =',minval(tcg_racg)
-      
          write(0,*) 'max tmr_racg =',maxval(tmr_racg)
          write(0,*) 'min tmr_racg =',minval(tmr_racg)
-
          write(0,*) 'max tcr_gacr =',maxval(tcr_gacr)
          write(0,*) 'min tcr_gacr =',minval(tcr_gacr)
-
          write(0,*) 'max tmg_gacr =',maxval(tmg_gacr)
          write(0,*) 'min tmg_gacr =',minval(tmg_gacr)
-
          write(0,*) 'max tnr_racg =',maxval(tnr_racg)
          write(0,*) 'min tnr_racg =',minval(tnr_racg)
-
          write(0,*) 'max tnr_gacr =',maxval(tnr_gacr)
          write(0,*) 'min tnr_gacr =',minval(tnr_gacr)
-!        DO ig1 = 1, ntb_g1
-!        DO ig  = 1, ntb_g
-!        DO ir1 = 1, ntb_r1
-!           write(0,201) (tcg_racg(ig1,ig,ir1,ir),ir=1,ntb_r)
-!           write(0,*)
-!        ENDDO
-!        DO ir1 = 1, ntb_r1
-!           write(0,201) (tmr_racg(ig1,ig,ir1,ir),ir=1,ntb_r)
-!           write(0,*)
-!        ENDDO
-!        DO ir1 = 1, ntb_r1
-!           write(0,201) (tcr_gacr(ig1,ig,ir1,ir),ir=1,ntb_r)
-!           write(0,*)
-!        ENDDO
-!        DO ir1 = 1, ntb_r1
-!           write(0,201) (tmg_gacr(ig1,ig,ir1,ir),ir=1,ntb_r)
-!           write(0,*)
-!        ENDDO
-!        DO ir1 = 1, ntb_r1
-!           write(0,201) (tnr_racg(ig1,ig,ir1,ir),ir=1,ntb_r)
-!           write(0,*)
-!        ENDDO
-!        DO ir1 = 1, ntb_r1
-!           write(0,201) (tnr_gacr(ig1,ig,ir1,ir),ir=1,ntb_r)
-!           write(0,*)
-!        ENDDO
-!        ENDDO
-!        ENDDO
-!        write(0,*) '       end read table_qr_acr_qg.dat'
-!    201 FORMAT(10(1x,d15.8))
 
 !..Rain collecting snow &amp; snow collecting rain.
-         open(unit=11,file='./LOOKUP_TABLES/table_qr_acr_qs.dat', &amp;
-              form='unformatted',status='old',action='read')
+         open(unit=11,file='MP_THOMPSON_QRacrQS.DBL',form='UNFORMATTED',status='OLD',action='READ', &amp;
+              iostat=istat)
+         if(istat /= open_OK) &amp;
+            call physics_error_fatal('subroutine thompson_init: ' // &amp;
+                                     'failure opening MP_THOMPSON_QRacrQS.DBL')
          read(11) tcs_racs1
          read(11) tmr_racs1
          read(11) tcs_racs2
@@ -795,42 +750,34 @@
          read(11) tnr_sacr1
          read(11) tnr_sacr2
          close(unit=11)
-         write(0,*) '       end read table_qr_acr_qs.dat'
-         write(0,*)
-         write(0,*) '--- end subroutine qr_acr_qs:'
+         write(0,*) '--- end read MP_THOMPSON_QRacrQS.DBL'
          write(0,*) 'max tcs_racs1 =',maxval(tcs_racs1)
          write(0,*) 'min tcs_racs1 =',minval(tcs_racs1)      
-
          write(0,*) 'max tmr_racs1 =',maxval(tmr_racs1)
          write(0,*) 'min tmr_racs1 =',minval(tmr_racs1)
-
          write(0,*) 'max tcr_sacr1 =',maxval(tcr_sacr1)
          write(0,*) 'min tcr_sacr1 =',minval(tcr_sacr1)
-
          write(0,*) 'max tms_sacr1 =',maxval(tms_sacr1)      
          write(0,*) 'min tms_sacr1 =',minval(tms_sacr1)      
-
          write(0,*) 'max tcr_sacr2 =',maxval(tcr_sacr2)
          write(0,*) 'min tcr_sacr2 =',minval(tcr_sacr2)
-
          write(0,*) 'max tcr_sacr2 =',maxval(tcr_sacr2)
          write(0,*) 'min tcr_sacr2 =',minval(tcr_sacr2)
-
          write(0,*) 'max tnr_racs1 =',maxval(tnr_racs1)
          write(0,*) 'min tnr_racs1 =',minval(tnr_racs1)
-
          write(0,*) 'max tnr_racs2 =',maxval(tnr_racs2)      
          write(0,*) 'min tnr_racs2 =',minval(tnr_racs2)      
-
          write(0,*) 'max tnr_sacr1 =',maxval(tnr_sacr1)
          write(0,*) 'min tnr_sacr1 =',minval(tnr_sacr1)      
-
          write(0,*) 'max tnr_sacr2 =',maxval(tnr_sacr2)
          write(0,*) 'min tnr_sacr2 =',minval(tnr_sacr2)      
 
 !..Cloud water and rain freezing (Bigg, 1953).
-         open(unit=11,file='./LOOKUP_TABLES/table_freezeH2O.dat', &amp;
-              form='unformatted',status='old',action='read')
+         open(unit=11,file='MP_THOMPSON_freezeH2O.DBL',form='UNFORMATTED',status='OLD',action='READ', &amp;
+              iostat=istat)
+         if(istat /= open_OK) &amp;
+            call physics_error_fatal('subroutine thompson_init: ' // &amp;
+                                     'failure opening MP_THOMPSON_freezeH2O.DBL')
          read(11) tpi_qrfz
          read(11) tni_qrfz
          read(11) tpg_qrfz
@@ -838,66 +785,59 @@
          read(11) tpi_qcfz
          read(11) tni_qcfz
          close(unit=11)
-         write(0,*) '       end read table_freezeH2O.dat'
-         write(0,*)
-         write(0,*) '--- end subroutine freezeH2O:'
+         write(0,*) '--- end read MP_THOMPSON_freezeH2O.DBL:'
          write(0,*) 'max tpi_qrfz =',maxval(tpi_qrfz)
          write(0,*) 'min tpi_qrfz =',minval(tpi_qrfz)      
-
          write(0,*) 'max tni_qrfz =',maxval(tni_qrfz)
          write(0,*) 'min tni_qrfz =',minval(tni_qrfz)      
-
          write(0,*) 'max tpg_qrfz =',maxval(tpg_qrfz)
          write(0,*) 'min tpg_qrfz =',minval(tpg_qrfz)      
-
          write(0,*) 'max tnr_qrfz =',maxval(tnr_qrfz)
          write(0,*) 'min tnr_qrfz =',minval(tnr_qrfz)      
-
          write(0,*) 'max tpi_qcfz =',maxval(tpi_qcfz)
          write(0,*) 'min tpi_qcfz =',minval(tpi_qcfz)      
-
          write(0,*) 'max tni_qcfz =',maxval(tni_qcfz)
          write(0,*) 'min tni_qcfz =',minval(tni_qcfz)      
 
 !..Conversion of some ice mass into snow category.
-         open(unit=11,file='./LOOKUP_TABLES/table_qi_aut_qs.dat', &amp;
-              form='unformatted',status='old',action='read')
+         open(unit=11,file='MP_THOMPSON_QIautQS.DBL',form='UNFORMATTED',status='OLD',action='READ', &amp;
+              iostat=istat)
+         if(istat /= open_OK) &amp;
+            call physics_error_fatal('subroutine thompson_init: ' // &amp;
+                                     'failure opening MP_THOMPSON_QIautQS.DBL')
          read(11) tpi_ide
          read(11) tps_iaus
          read(11) tni_iaus
          close(unit=11)
-         write(0,*) '       end read table_qi_aut_qs.dat'
-         write(0,*) '--- end subroutine qi_aut_qs:'
+         write(0,*) '--- end read MP_THOMPSON_QIautQS.DBL '
          write(0,*) 'max tps_iaus =',maxval(tps_iaus)
-         write(0,*) 'min tps_iaus =',minval(tps_iaus)      
-      
+         write(0,*) 'min tps_iaus =',minval(tps_iaus)            
          write(0,*) 'max tni_iaus =',maxval(tni_iaus)
          write(0,*) 'min tni_iaus =',minval(tni_iaus)      
 
-         write(0,*) '    end pre-calculated look-up tables'
-         iiwarm = .false.
+#else
+      if (.not. iiwarm) then
 
-      elseif (.not. iiwarm) then
-
 !..Rain collecting graupel &amp; graupel collecting rain.
-!     CALL wrf_debug(200, '  creating rain collecting graupel table')
+      CALL wrf_debug(200, '  creating rain collecting graupel table')
       call qr_acr_qg
 
 !..Rain collecting snow &amp; snow collecting rain.
-!     CALL wrf_debug(200, '  creating rain collecting snow table')
+      CALL wrf_debug(200, '  creating rain collecting snow table')
       call qr_acr_qs
 
 !..Cloud water and rain freezing (Bigg, 1953).
-!     CALL wrf_debug(200, '  creating freezing of water drops table')
+      CALL wrf_debug(200, '  creating freezing of water drops table')
       call freezeH2O
 
 !..Conversion of some ice mass into snow category.
-!     CALL wrf_debug(200, '  creating ice converting to snow table')
+      CALL wrf_debug(200, '  creating ice converting to snow table')
       call qi_aut_qs
 
       endif
 
-!     CALL wrf_debug(150, ' ... DONE microphysical lookup tables')
+      CALL wrf_debug(150, ' ... DONE microphysical lookup tables')
+#endif
 
       endif
 
@@ -1078,7 +1018,11 @@
             elseif (qc1d(k) .lt. 0.0) then
              write(mp_debug,*) 'WARNING, negative qc ', qc1d(k),        &amp;
                         ' at i,j,k=', i,j,k
-!            CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+             call physics_error_fatal(mp_debug)
+#else
+             CALL wrf_debug(150, mp_debug)
+#endif
             endif
             if (qr1d(k) .gt. qr_max) then
              imax_qr = i
@@ -1088,7 +1032,11 @@
             elseif (qr1d(k) .lt. 0.0) then
              write(mp_debug,*) 'WARNING, negative qr ', qr1d(k),        &amp;
                         ' at i,j,k=', i,j,k
-!            CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+             call physics_error_fatal(mp_debug)
+#else
+             CALL wrf_debug(150, mp_debug)
+#endif
             endif
             if (nr1d(k) .gt. nr_max) then
              imax_nr = i
@@ -1098,7 +1046,11 @@
             elseif (nr1d(k) .lt. 0.0) then
              write(mp_debug,*) 'WARNING, negative nr ', nr1d(k),        &amp;
                         ' at i,j,k=', i,j,k
-!            CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+             call physics_error_fatal(mp_debug)
+#else
+             CALL wrf_debug(150, mp_debug)
+#endif
             endif
             if (qs1d(k) .gt. qs_max) then
              imax_qs = i
@@ -1108,7 +1060,11 @@
             elseif (qs1d(k) .lt. 0.0) then
              write(mp_debug,*) 'WARNING, negative qs ', qs1d(k),        &amp;
                         ' at i,j,k=', i,j,k
-!            CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+             call physics_error_fatal(mp_debug)
+#else
+             CALL wrf_debug(150, mp_debug)
+#endif
             endif
             if (qi1d(k) .gt. qi_max) then
              imax_qi = i
@@ -1118,7 +1074,11 @@
             elseif (qi1d(k) .lt. 0.0) then
              write(mp_debug,*) 'WARNING, negative qi ', qi1d(k),        &amp;
                         ' at i,j,k=', i,j,k
-!            CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+             call physics_error_fatal(mp_debug)
+#else
+             CALL wrf_debug(150, mp_debug)
+#endif
             endif
             if (qg1d(k) .gt. qg_max) then
              imax_qg = i
@@ -1128,7 +1088,11 @@
             elseif (qg1d(k) .lt. 0.0) then
              write(mp_debug,*) 'WARNING, negative qg ', qg1d(k),        &amp;
                         ' at i,j,k=', i,j,k
-!            CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+             call physics_error_fatal(mp_debug)
+#else
+             CALL wrf_debug(150, mp_debug)
+#endif
             endif
             if (ni1d(k) .gt. ni_max) then
              imax_ni = i
@@ -1138,7 +1102,11 @@
             elseif (ni1d(k) .lt. 0.0) then
              write(mp_debug,*) 'WARNING, negative ni ', ni1d(k),        &amp;
                         ' at i,j,k=', i,j,k
-!            CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+             call physics_error_fatal(mp_debug)
+#else
+             CALL wrf_debug(150, mp_debug)
+#endif
             endif
             if (qv1d(k) .lt. 0.0) then
              if (k.lt.kte-2 .and. k.gt.kts+1) then
@@ -1148,7 +1116,11 @@
              endif
              write(mp_debug,*) 'WARNING, negative qv ', qv1d(k),        &amp;
                         ' at i,j,k=', i,j,k
-!            CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+             call physics_error_fatal(mp_debug)
+#else
+             CALL wrf_debug(150, mp_debug)
+#endif
             endif
          enddo
 
@@ -1172,7 +1144,11 @@
          'qg: ', qg_max, '(', imax_qg, ',', jmax_qg, ',', kmax_qg, ')', &amp;
          'ni: ', ni_max, '(', imax_ni, ',', jmax_ni, ',', kmax_ni, ')', &amp;
          'nr: ', nr_max, '(', imax_nr, ',', jmax_nr, ',', kmax_nr, ')'
-!     CALL wrf_debug(150, mp_debug)
+#if defined(non_hydrostatic_core) || defined(hydrostatic_core)
+      call physics_message(mp_debug)
+#else
+      CALL wrf_debug(150, mp_debug)
+#endif
 ! END DEBUG - GT
 
       do i = 1, 256
@@ -3771,4 +3747,4 @@
 
 !+---+-----------------------------------------------------------------+
 END MODULE module_mp_thompson
-!+---+-----------------------------------------------------------------+
\ No newline at end of file
+!+---+-----------------------------------------------------------------+

</font>
</pre>