Ignore:
Timestamp:
Mar 26, 2018 9:39:22 AM (6 years ago)
Author:
maronga
Message:

renamed all Fortran NAMELISTS

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r2894 r2932  
    2727! -----------------
    2828! $Id$
     29! renamed chemistry_par to chemistry_parameters
     30!
     31! 2894 2018-03-15 09:17:58Z Giersch
    2932! Calculations of the index range of the subdomain on file which overlaps with
    3033! the current subdomain are already done in read_restart_data_mod,
     
    600603!
    601604!-- Set initial concentration of profiles prescribed by parameters cs_profile
    602 !-- and cs_heights in the namelist &chemistry_par
     605!-- and cs_heights in the namelist &chemistry_parameters
    603606!-- (todo (FK): chem_init_profiles not ready yet, has some bugs)
    604607!     CALL chem_init_profiles
     
    780783! Description:
    781784! ------------
    782 !> Subroutine defining parin for &chemistry_par for chemistry model
     785!> Subroutine defining parin for &chemistry_parameters for chemistry model
    783786!------------------------------------------------------------------------------!
    784787   SUBROUTINE chem_parin
     
    797800      REAL(wp), DIMENSION(nmaxfixsteps) ::   my_steps   !< List of fixed timesteps   my_step(1) = 0.0 automatic stepping
    798801
    799       NAMELIST /chemistry_par/   bc_cs_b,                                &
    800                                  bc_cs_t,                                &
    801                                  call_chem_at_all_substeps,              &
    802                                  chem_debug0,                            &
    803                                  chem_debug1,                            &
    804                                  chem_debug2,                            &
    805                                  chem_gasphase_on,                       &
    806                                  cs_heights,                             &
    807                                  cs_name,                                &
    808                                  cs_profile,                             &
    809                                  cs_profile_name,                        &
    810                                  cs_surface,                             &
    811                                  emiss_factor_main,                      &
    812                                  emiss_factor_side,                      &                     
    813                                  icntrl,                                 &
    814                                  main_street_id,                         &
    815                                  max_street_id,                          &
    816                                  my_steps,                               &
    817                                  rcntrl,                                 &
    818                                  side_street_id,                         &
    819                                  photolysis_scheme,                      &
    820                                  wall_csflux,                            &
    821                                  cs_vertical_gradient,                   &
    822                                  top_csflux,                             &
    823                                  surface_csflux,                         &
    824                                  surface_csflux_name,                    &
    825                                  cs_surface_initial_change,              &
    826                                  cs_vertical_gradient_level
     802      NAMELIST /chemistry_parameters/   bc_cs_b,                          &
     803                                        bc_cs_t,                          &
     804                                        call_chem_at_all_substeps,        &
     805                                        chem_debug0,                      &
     806                                        chem_debug1,                      &
     807                                        chem_debug2,                      &
     808                                        chem_gasphase_on,                 &
     809                                        cs_heights,                       &
     810                                        cs_name,                          &
     811                                        cs_profile,                       &
     812                                        cs_profile_name,                  &
     813                                        cs_surface,                       &
     814                                        emiss_factor_main,                &
     815                                        emiss_factor_side,                &                     
     816                                        icntrl,                           &
     817                                        main_street_id,                   &
     818                                        max_street_id,                    &
     819                                        my_steps,                         &
     820                                        rcntrl,                           &
     821                                        side_street_id,                   &
     822                                        photolysis_scheme,                &
     823                                        wall_csflux,                      &
     824                                        cs_vertical_gradient,             &
     825                                        top_csflux,                       &
     826                                        surface_csflux,                   &
     827                                        surface_csflux_name,              &
     828                                        cs_surface_initial_change,        &
     829                                        cs_vertical_gradient_level
    827830                             
    828831!-- analogue to chem_names(nspj) we could invent chem_surfaceflux(nspj) and chem_topflux(nspj)
    829832!-- so this way we could prescribe a specific flux value for each species
    830 !>  chemistry_par for initial profiles
     833!>  chemistry_parameters for initial profiles
    831834!>  cs_names = 'O3', 'NO2', 'NO', ...   to set initial profiles)
    832835!>  cs_heights(1,:) = 0.0, 100.0, 500.0, 2000.0, .... (height levels where concs will be prescribed for O3)
     
    839842!--   Read chem namelist   
    840843!--   (todo: initialize these parameters in declaration part, do this for
    841 !--          all chemistry_par namelist parameters)
     844!--          all chemistry_parameters namelist parameters)
    842845      icntrl    = 0
    843846      rcntrl    = 0.0_wp
     
    851854      REWIND ( 11 )
    852855      line = ' '
    853       DO   WHILE ( INDEX( line, '&chemistry_par' ) == 0 )
     856      DO   WHILE ( INDEX( line, '&chemistry_parameters' ) == 0 )
    854857         READ ( 11, '(A)', END=10 )  line
    855858      ENDDO
     
    857860!
    858861!--   Read chemistry namelist
    859       READ ( 11, chemistry_par )                         
     862      READ ( 11, chemistry_parameters )                         
    860863!
    861864!--   Enable chemistry model
     
    17731776!
    17741777! !
    1775 ! !-- Writing out input parameters that are not part of chemistry_par namelist
    1776 ! !-- (namelist parameters are anyway read in again in case of restart)
     1778! !-- Writing out input parameters that are not part of chemistry_parameters
     1779! !-- namelist (namelist parameters are anyway read in again in case of restart)
    17771780!     DO lsp = 1, nvar
    17781781!        CALL wrd_write_string( 'conc_pr_init_'//chem_species(lsp)%name )
Note: See TracChangeset for help on using the changeset viewer.