Changeset 3737 for palm/trunk/SOURCE/chemistry_model_mod.f90
- Timestamp:
- Feb 12, 2019 4:57:06 PM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chemistry_model_mod.f90
r3719 r3737 27 27 ! ----------------- 28 28 ! $Id$ 29 ! Enable mesoscale offline nesting for chemistry variables as well as 30 ! initialization of chemistry via dynamic input file. 31 ! 32 ! 3719 2019-02-06 13:10:18Z kanani 29 33 ! Resolved cpu logpoint overlap with all progn.equations, moved cpu_log call 30 34 ! to prognostic_equations for better overview … … 1408 1412 ! TRIM(chem_species(lsp)%name) 1409 1413 IF (av == 0) THEN 1414 write(9,*) "before", TRIM(chem_species(lsp)%name), fill_value 1415 flush(9) 1410 1416 DO i = nxl, nxr 1411 1417 DO j = nys, nyn 1412 1418 DO k = nzb_do, nzt_do 1419 ! write(9,*) k, j, i 1420 ! flush(9) 1421 ! write(9) chem_species(lsp)%conc(k,j,i) 1422 ! flush(9) 1423 ! write(9) "fill", fill_value 1424 ! flush(9) 1413 1425 local_pf(i,j,k) = MERGE( & 1414 1426 chem_species(lsp)%conc(k,j,i), & … … 1745 1757 USE chem_emissions_mod, & 1746 1758 ONLY: chem_emissions_init 1759 1760 USE netcdf_data_input_mod, & 1761 ONLY: init_3d 1747 1762 1748 1763 IMPLICIT NONE 1749 1764 1765 INTEGER(iwp) :: i !< running index x dimension 1766 INTEGER(iwp) :: j !< running index y dimension 1767 INTEGER(iwp) :: n !< running index for chemical species 1750 1768 1751 1769 IF ( do_emis ) CALL chem_emissions_init 1770 ! 1771 !-- Chemistry variables will be initialized if availabe from dynamic 1772 !-- input file. Note, it is possible to initialize only part of the chemistry 1773 !-- variables from dynamic input. 1774 IF ( INDEX( initializing_actions, 'inifor' ) /= 0 ) THEN 1775 DO n = 1, nspec 1776 IF ( init_3d%from_file_chem(n) ) THEN 1777 DO i = nxlg, nxrg 1778 DO j = nysg, nyng 1779 chem_species(n)%conc(:,j,i) = init_3d%chem_init(:,n) 1780 ENDDO 1781 ENDDO 1782 ENDIF 1783 ENDDO 1784 ENDIF 1752 1785 1753 1786 … … 1764 1797 SUBROUTINE chem_init_internal 1765 1798 1766 USE control_parameters, &1799 USE control_parameters, & 1767 1800 ONLY: message_string, io_blocks, io_group, turbulent_inflow 1768 USE arrays_3d, &1801 USE arrays_3d, & 1769 1802 ONLY: mean_inflow_profiles 1770 1803 USE pegrid 1771 1804 1772 1805 USE netcdf_data_input_mod, & 1773 ONLY: chem_emis, chem_emis_att, netcdf_data_input_chemistry_data 1806 ONLY: chem_emis, chem_emis_att, input_pids_dynamic, init_3d, & 1807 netcdf_data_input_chemistry_data 1774 1808 1775 1809 IMPLICIT NONE … … 1839 1873 !-- Initial concentration of profiles is prescribed by parameters cs_profile 1840 1874 !-- and cs_heights in the namelist &chemistry_parameters 1841 CALL chem_init_profiles 1875 CALL chem_init_profiles 1876 ! 1877 !-- In case there is dynamic input file, create a list of names for chemistry 1878 !-- initial input files. Also, initialize array that indicates whether the 1879 !-- respective variable is on file or not. 1880 IF ( input_pids_dynamic ) THEN 1881 ALLOCATE( init_3d%var_names_chem(1:nspec) ) 1882 ALLOCATE( init_3d%from_file_chem(1:nspec) ) 1883 init_3d%from_file_chem(:) = .FALSE. 1884 1885 DO lsp = 1, nspec 1886 init_3d%var_names_chem(lsp) = init_3d%init_char // TRIM( chem_species(lsp)%name ) 1887 ENDDO 1888 ENDIF 1889 1842 1890 1843 1891 1844 1892 ! 1845 1893 !-- Initialize model variables 1846 1847 1848 1894 IF ( TRIM( initializing_actions ) /= 'read_restart_data' .AND. & 1849 1895 TRIM( initializing_actions ) /= 'cyclic_fill' ) THEN
Note: See TracChangeset
for help on using the changeset viewer.