Changeset 3833


Ignore:
Timestamp:
Mar 28, 2019 3:04:04 PM (5 years ago)
Author:
forkel
Message:

removed USE chem_gasphase_mod from chem_modules, apply USE chem_gasphase for nvar, nspec, cs_mech and spc_names instead

Location:
palm/trunk
Files:
26 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/Makefile

    r3745 r3833  
    874874        modules.o
    875875chem_modules.o: \
    876         chem_gasphase_mod.o \
    877876        mod_kinds.o \
    878877        modules.o
     
    14401439        bulk_cloud_model_mod.o \
    14411440        chemistry_model_mod.o \
    1442         chem_modules.o \
     1441        chem_gasphase_mod.o \
    14431442        mod_kinds.o \
    14441443        mod_particle_attributes.o \
     
    15111510        buoyancy.o \
    15121511        chemistry_model_mod.o \
     1512        chem_gasphase_mod.o \
    15131513        chem_modules.o \
    15141514        chem_photolysis_mod.o \
     
    16261626        basic_constants_and_equations_mod.o \
    16271627        bulk_cloud_model_mod.o \
     1628        chem_gasphase_mod.o \
    16281629        chem_modules.o \
    16291630        exchange_horiz_2d.o \
     
    16341635        urban_surface_mod.o
    16351636surface_mod.o: \
     1637        chem_gasphase_mod.o \
    16361638        chem_modules.o \
    16371639        model_1d_mod.o \
     
    16701672        chem_emissions_mod.o \
    16711673        chemistry_model_mod.o \
     1674        chem_gasphase_mod.o \
    16721675        chem_modules.o \
    16731676        cpulog_mod.o \
     
    18471850        cpulog_mod.o \
    18481851        chemistry_model_mod.o \
    1849         chem_modules.o \
     1852        chem_gasphase_mod.o \
    18501853        mod_kinds.o \
    18511854        modules.o \
  • palm/trunk/SOURCE/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:40 2019
     119! Time                 : Thu Mar 28 15:59:30 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    191194!
    192195! File                 : chem_gasphase_mod_Global.f90
    193 ! Time                 : Wed Mar 27 09:51:40 2019
     196! Time                 : Thu Mar 28 15:59:30 2019
    194197! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    195198! Equation file        : chem_gasphase_mod.kpp
     
    256259!
    257260! File                 : chem_gasphase_mod_JacobianSP.f90
    258 ! Time                 : Wed Mar 27 09:51:40 2019
     261! Time                 : Thu Mar 28 15:59:30 2019
    259262! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    260263! Equation file        : chem_gasphase_mod.kpp
     
    300303!
    301304! File                 : chem_gasphase_mod_Monitor.f90
    302 ! Time                 : Wed Mar 27 09:51:40 2019
     305! Time                 : Thu Mar 28 15:59:30 2019
    303306! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    304307! Equation file        : chem_gasphase_mod.kpp
     
    362365!
    363366! File                 : chem_gasphase_mod_Initialize.f90
    364 ! Time                 : Wed Mar 27 09:51:40 2019
     367! Time                 : Thu Mar 28 15:59:30 2019
    365368! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    366369! Equation file        : chem_gasphase_mod.kpp
     
    388391!
    389392! File                 : chem_gasphase_mod_Integrator.f90
    390 ! Time                 : Wed Mar 27 09:51:40 2019
     393! Time                 : Thu Mar 28 15:59:30 2019
    391394! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    392395! Equation file        : chem_gasphase_mod.kpp
     
    446449!
    447450! File                 : chem_gasphase_mod_LinearAlgebra.f90
    448 ! Time                 : Wed Mar 27 09:51:40 2019
     451! Time                 : Thu Mar 28 15:59:30 2019
    449452! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    450453! Equation file        : chem_gasphase_mod.kpp
     
    473476!
    474477! File                 : chem_gasphase_mod_Jacobian.f90
    475 ! Time                 : Wed Mar 27 09:51:40 2019
     478! Time                 : Thu Mar 28 15:59:30 2019
    476479! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    477480! Equation file        : chem_gasphase_mod.kpp
     
    500503!
    501504! File                 : chem_gasphase_mod_Function.f90
    502 ! Time                 : Wed Mar 27 09:51:40 2019
     505! Time                 : Thu Mar 28 15:59:30 2019
    503506! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    504507! Equation file        : chem_gasphase_mod.kpp
     
    529532!
    530533! File                 : chem_gasphase_mod_Rates.f90
    531 ! Time                 : Wed Mar 27 09:51:40 2019
     534! Time                 : Thu Mar 28 15:59:30 2019
    532535! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    533536! Equation file        : chem_gasphase_mod.kpp
     
    555558!
    556559! File                 : chem_gasphase_mod_Util.f90
    557 ! Time                 : Wed Mar 27 09:51:40 2019
     560! Time                 : Thu Mar 28 15:59:30 2019
    558561! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    559562! Equation file        : chem_gasphase_mod.kpp
     
    589592  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    590593  !
    591   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     594  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     595  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    592596  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     597  ! t_steps: fixed time steps in vector mode
    593598  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    594599
  • palm/trunk/SOURCE/chem_modules.f90

    r3827 r3833  
    2727! -----------------
    2828! $Id$
     29! removed USE chem_gasphase_mod
     30!
     31! 3827 2019-03-27 17:20:32Z forkel
    2932! some formatting  and reordering (ecc)
    3033!
     
    7578 MODULE chem_modules
    7679
    77     USE chem_gasphase_mod,                                                     &   
    78         ONLY: cs_mech, nspec, nvar, spc_names
    79 
    8080    USE control_parameters,                                                    &
    8181        ONLY: varnamelength
     
    8484
    8585    IMPLICIT NONE
    86 
    87     PUBLIC cs_mech
    88     PUBLIC nspec
    89     PUBLIC nvar
    90     PUBLIC spc_names
    9186
    9287    CHARACTER (LEN=20)                ::  bc_cs_b             = 'dirichlet'         !< namelist parameter
  • palm/trunk/SOURCE/chemistry_model_mod.f90

    r3824 r3833  
    2727! -----------------
    2828! $Id: chemistry_model_mod.f90 3784 2019-03-05 14:16:20Z banzhafs
     29! added cs_mech to USE chem_gasphase_mod
     30!
     31! 3784 2019-03-05 14:16:20Z banzhafs
    2932! renamed get_mechanismname to get_mechanism_name
    3033! renamed do_emiss to emissions_anthropogenic and do_depo to deposition_dry (ecc)
     
    257260! ------------
    258261!> Chemistry model for PALM-4U
     262!> @todo Extend chem_species type by nspec and nvar as addititional elements
    259263!> @todo Adjust chem_rrd_local to CASE structure of others modules. It is not
    260264!>       allowed to use the chemistry model in a precursor run and additionally
    261265!>       not using it in a main run
    262266!> @todo Update/clean-up todo list! (FK)
    263 !> @todo Set proper fill values (/= 0) for chem output arrays! (FK)
    264267!> @todo Add routine chem_check_parameters, add checks for inconsistent or
    265268!>       unallowed parameter settings.
    266269!>       CALL of chem_check_parameters from check_parameters. (FK)
    267 !> @todo Make routine chem_header available, CALL from header.f90
    268 !>       (see e.g. how it is done in routine lsm_header in
    269 !>        land_surface_model_mod.f90). chem_header should include all setup
    270 !>        info about chemistry parameter settings. (FK)
    271270!> @todo Implement turbulent inflow of chem spcs in inflow_turbulence.
    272271!> @todo Separate boundary conditions for each chem spcs to be implemented
     
    307306
    308307    USE chem_gasphase_mod,                                                                         &
    309          ONLY:  atol, chem_gasphase_integrate, get_mechanism_name, nkppctrl, nmaxfixsteps,         &
    310          nphot, nreact, nspec, nvar, phot_names, rtol, spc_names, t_steps, vl_dim
     308         ONLY:  atol, chem_gasphase_integrate, cs_mech, get_mechanism_name, nkppctrl,              &
     309         nmaxfixsteps, nphot, nreact, nspec, nvar, phot_names, rtol, spc_names, t_steps, vl_dim
    311310
    312311    USE chem_modules
  • palm/trunk/SOURCE/multi_agent_system_mod.f90

    r3766 r3833  
    2525! -----------------
    2626! $Id$
     27! replaced nspec by nvar: only variable species should bconsidered, fixed species are not relevant
     28!
     29! 3766 2019-02-26 16:23:41Z raasch
    2730! save attribute added to local targets to avoid outlive pointer target warning
    2831!
     
    30153018
    30163019!       USE chem_gasphase_mod,                                                  &
    3017 !           ONLY:  nspec
     3020!           ONLY:  nvar
    30183021
    30193022!       USE chemistry_model_mod,                                                &
     
    31083111! !--    Get indices of PM10 and PM2.5 species, if active
    31093112!        IF ( air_chemistry ) THEN
    3110 !           DO il = 1, nspec
     3113!           DO il = 1, nvar
    31113114! print*,chem_species(il)%name
    31123115! !              IF ( spec_name(1:4) == 'PM10' ) THEN 
  • palm/trunk/SOURCE/pmc_interface_mod.f90

    r3822 r3833  
    2525! -----------------
    2626! $Id$
     27! replaced USE chem_modules by USE chem_gasphase_mod
     28!
     29! 3822 2019-03-27 13:10:23Z hellstea
    2730! Temporary increase of the vertical dimension of the parent-grid arrays and
    2831! workarrc_t is cancelled as unnecessary.
     
    397400               roughness_length, topography, volume_flow
    398401
    399     USE chem_modules,                                                          &
     402    USE chem_gasphase_mod,                                                          &
    400403        ONLY:  nspec
    401404
  • palm/trunk/SOURCE/prognostic_equations.f90

    r3820 r3833  
    2525! -----------------
    2626! $Id$
     27! added USE chem_gasphase_mod for nvar, nspec and spc_names
     28!
     29! 3820 2019-03-27 11:53:41Z forkel
    2730! renamed do_depo to deposition_dry (ecc)
    2831!
     
    378381               deposition_dry
    379382
     383    USE chem_gasphase_mod,                                                     &
     384        ONLY:  nspec, nvar, spc_names
     385
    380386    USE chem_photolysis_mod,                                                   &
    381387        ONLY:  photolysis_control
     
    383389    USE chemistry_model_mod,                                                   &
    384390        ONLY:  chem_boundary_conds, chem_depo, chem_integrate,                 &
    385                chem_prognostic_equations, chem_species,                        &
    386                nspec, nvar, spc_names
     391               chem_prognostic_equations, chem_species
    387392
    388393    USE control_parameters,                                                    &
  • palm/trunk/SOURCE/salsa_mod.f90

    r3787 r3833  
    2626! -----------------
    2727! $Id$
     28! added USE chem_gasphase_mod for nvar, nspec and spc_names
     29!
     30! 3787 2019-03-07 08:43:54Z raasch
    2831! unused variables removed
    2932!
     
    9699        ONLY:  c_p, g, p_0, pi, r_d
    97100 
     101    USE chem_gasphase_mod,                                                     &
     102        ONLY:  nspec, nvar, spc_names
     103
    98104    USE chemistry_model_mod,                                                   &
    99         ONLY:  chem_species, nspec, nvar, spc_names
     105        ONLY:  chem_species
    100106
    101107    USE chem_modules,                                                          &
  • palm/trunk/SOURCE/surface_layer_fluxes_mod.f90

    r3787 r3833  
    2626! -----------------
    2727! $Id$
     28! added USE chem_gasphase_mod
     29!
     30! 3787 2019-03-07 08:43:54Z raasch
    2831! unused variables removed
    2932!
     
    255258    USE basic_constants_and_equations_mod,                                     &
    256259        ONLY:  g, kappa, lv_d_cp, pi, rd_d_rv
     260
     261    USE chem_gasphase_mod,                                                     &
     262        ONLY:  nvar
    257263
    258264    USE chem_modules,                                                          &
  • palm/trunk/SOURCE/surface_mod.f90

    r3772 r3833  
    2626! -----------------
    2727! $Id$
     28! added USE chem_gasphase_mod (chem_modules will not transport nvar and nspec anymore)
     29!
     30! 3772 2019-02-28 15:51:57Z suehring
    2831! small change in the todo's
    2932!
     
    270273        ONLY:  heatflux_input_conversion, momentumflux_input_conversion,       &
    271274               rho_air, rho_air_zw, zu, zw, waterflux_input_conversion
     275
     276    USE chem_gasphase_mod,                                                     &
     277        ONLY:  nvar, spc_names
    272278
    273279    USE chem_modules
  • palm/trunk/SOURCE/time_integration.f90

    r3820 r3833  
    2525! -----------------
    2626! $Id$
     27! added USE chem_gasphase_mod, replaced nspec by nvar since fixed compounds are not integrated
     28!
     29! 3820 2019-03-27 11:53:41Z forkel
    2730! renamed do_emiss to emissions_anthropogenic (ecc)
    2831!
     
    489492        ONLY:  chem_emissions_setup
    490493
     494    USE chem_gasphase_mod,                                                                         &
     495        ONLY:  nvar
     496
    491497    USE chem_modules,                                                                              &
    492         ONLY:  bc_cs_t_val, cs_name, emissions_anthropogenic, nspec, nspec_out
     498        ONLY:  bc_cs_t_val, cs_name, emissions_anthropogenic, nspec_out
    493499
    494500    USE chemistry_model_mod,                                                                       &
     
    844850           bc_q_t_val  = ( q_init(nzt+1) - q_init(nzt) ) / dzu(nzt+1)
    845851           IF ( air_chemistry )  THEN
    846               DO  lsp = 1, nspec
     852              DO  lsp = 1, nvar
    847853                 bc_cs_t_val = (  chem_species(lsp)%conc_pr_init(nzt+1)                            &
    848854                                - chem_species(lsp)%conc_pr_init(nzt) )                            &
     
    10071013          IF ( passive_scalar )  CALL exchange_horiz( s_p, nbgp )
    10081014          IF ( air_chemistry )  THEN
    1009              DO  lsp = 1, nspec
     1015             DO  lsp = 1, nvar
    10101016                CALL exchange_horiz( chem_species(lsp)%conc_p, nbgp )
    10111017!
     
    11101116
    11111117                IF ( air_chemistry )  THEN
    1112                    DO  n = 1, nspec     
     1118                   DO  n = 1, nvar     
    11131119                      CALL exchange_horiz( chem_species(n)%conc, nbgp )
    11141120                   ENDDO
  • palm/trunk/SOURCE/virtual_measurement_mod.f90

    r3766 r3833  
    2525! -----------------
    2626! $Id$
     27! renamed nvar to nmeas, replaced USE chem_modules by USE chem_gasphase_mod and nspec by nvar
     28!
     29! 3766 2019-02-26 16:23:41Z raasch
    2730! unused variables removed
    2831!
     
    7679        ONLY:  q, pt, u, v, w, zu, zw
    7780
    78     USE chem_modules,                                                          &
    79         ONLY:  nspec
     81    USE chem_gasphase_mod,                                                     &
     82        ONLY:  nvar
    8083
    8184    USE chemistry_model_mod,                                                   &
     
    132135       INTEGER(iwp) ::  ns_tot = 0      !< total number of observation coordinates, for atmospheric measurements
    133136       INTEGER(iwp) ::  ntraj           !< number of trajectories of a measurement
    134        INTEGER(iwp) ::  nvar            !< number of measured variables (atmosphere + soil)
     137       INTEGER(iwp) ::  nmeas           !< number of measured variables (atmosphere + soil)
    135138       
    136139       INTEGER(iwp) ::  ns_soil = 0     !< number of observation coordinates on subdomain, for soil measurements
     
    551554!--    for a NULL to get the correct character length in order to compare
    552555!--    them with the list of allowed variables.
    553        vmea(l)%nvar   = 0
     556       vmea(l)%nmeas  = 0
    554557       DO ll = 1, SIZE( measured_variables_file )
    555558          IF ( measured_variables_file(ll)(1:1) /= CHAR(0)  .AND.              &
     
    569572                IF ( measured_variables_file(ll)(1:len_char) ==                &
    570573                     TRIM( list_allowed_variables(lll) ) )  THEN
    571                    vmea(l)%nvar = vmea(l)%nvar + 1
    572                    measured_variables(vmea(l)%nvar) =                          &
     574                   vmea(l)%nmeas = vmea(l)%nmeas + 1
     575                   measured_variables(vmea(l)%nmeas) =                         &
    573576                                       measured_variables_file(ll)(1:len_char)
    574577                ENDIF
     
    578581!
    579582!--    Allocate array for the measured variables names for the respective site.
    580        ALLOCATE( vmea(l)%measured_vars_name(1:vmea(l)%nvar) )
    581 
    582        DO  ll = 1, vmea(l)%nvar
     583       ALLOCATE( vmea(l)%measured_vars_name(1:vmea(l)%nmeas) )
     584
     585       DO  ll = 1, vmea(l)%nmeas
    583586          vmea(l)%measured_vars_name(ll) = TRIM( measured_variables(ll) )
    584587       ENDDO
     
    587590!--    chemistry mechanism.
    588591!        IF ( air_chemistry )  THEN
    589 !           DO  ll = 1, vmea(l)%nvar
     592!           DO  ll = 1, vmea(l)%nmeas
    590593!              chem_include = .FALSE.
    591 !              DO  n = 1, nspec
     594!              DO  n = 1, nvar
    592595!                 IF ( TRIM( vmea(l)%measured_vars_name(ll) ) ==                 &
    593596!                      TRIM( chem_species(n)%name ) )  chem_include = .TRUE.
     
    609612!--    as this would exceed memory requirements, particularly for trajectory
    610613!--    measurements.
    611        IF ( vmea(l)%nvar > 0 )  THEN
     614       IF ( vmea(l)%nmeas > 0 )  THEN
    612615!
    613616!--       For stationary measurements UTM coordinates are just one value and
     
    855858!
    856859!--       Allocate array to save the sampled values.
    857           ALLOCATE( vmea(l)%measured_vars(1:vmea(l)%ns,1:vmea(l)%nvar) )
     860          ALLOCATE( vmea(l)%measured_vars(1:vmea(l)%ns,1:vmea(l)%nmeas) )
    858861         
    859862          IF ( vmea(l)%soil_sampling )                                         &
    860863             ALLOCATE( vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil,           &
    861                                                   1:vmea(l)%nvar) )
     864                                                  1:vmea(l)%nmeas) )
    862865!
    863866!--       Initialize with _FillValues
    864           vmea(l)%measured_vars(1:vmea(l)%ns,1:vmea(l)%nvar) = vmea(l)%fillout
     867          vmea(l)%measured_vars(1:vmea(l)%ns,1:vmea(l)%nmeas) = vmea(l)%fillout
    865868          IF ( vmea(l)%soil_sampling )                                         &
    866              vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil,1:vmea(l)%nvar) =    &
     869             vmea(l)%measured_vars_soil(1:vmea(l)%ns_soil,1:vmea(l)%nmeas) =   &
    867870                                                                vmea(l)%fillout
    868871!
     
    955958                 WRITE ( 27 )  vmea(l)%ns_tot
    956959                 WRITE ( 27 )  'number of measured variables      '
    957                  WRITE ( 27 )  vmea(l)%nvar
     960                 WRITE ( 27 )  vmea(l)%nmeas
    958961                 WRITE ( 27 )  'variables                         '
    959962                 WRITE ( 27 )  vmea(l)%measured_vars_name(:)
     
    10131016!--              Skip binary writing if no observation points are defined on PE
    10141017                 IF ( vmea(l)%ns < 1  .AND.  vmea(l)%ns_soil < 1)  CYCLE                 
    1015                  DO  n = 1, vmea(l)%nvar
     1018                 DO  n = 1, vmea(l)%nmeas
    10161019                    WRITE( 27 )  vmea(l)%measured_vars_name(n)
    10171020                    IF ( vmea(l)%soil_sampling  .AND.                           &
     
    11061109!
    11071110!--     Loop over all variables measured at this site. 
    1108         DO  n = 1, vmea(l)%nvar
     1111        DO  n = 1, vmea(l)%nmeas
    11091112       
    11101113           SELECT CASE ( TRIM( vmea(l)%measured_vars_name(n) ) )
     
    12631266!--                 Run loop over all chemical species, if the measured
    12641267!--                 variable matches the interal name, sample the variable.
    1265                     DO  nn = 1, nspec                   
     1268                    DO  nn = 1, nvar                   
    12661269                       IF ( TRIM( chem_vars(1,ind_chem) ) ==                   &
    12671270                            TRIM( chem_species(nn)%name ) )  THEN                           
  • palm/trunk/UTIL/chemistry/gasphase_preproc/kpp4palm/src/create_kpp_module.C

    r3820 r3833  
    1313//Former revisions:
    1414//-----------------
    15 // renamed get_mechanismname to get_mechanism_name                        (26.03.2019, forkel):w
     15// alphabetic ordering of PUBLIC statments in templates/module_header     (28.03.2019, forkel)
     16//
     17// renamed get_mechanismname to get_mechanism_name                        (26.03.2019, forkel)
    1618//
    1719//
  • palm/trunk/UTIL/chemistry/gasphase_preproc/kpp4palm/templates/initialize_kpp_ctrl_template.f90

    r3789 r3833  
    2424  INTEGER, PARAMETER, PUBLIC :: NKPPCTRL = 20
    2525  !
    26   INTEGER,  DIMENSION(NKPPCTRL), PUBLIC     :: icntrl = 0
     26  ! Steering parameters for chemistry solver (see KPP domumentation)
     27  INTEGER, DIMENSION(NKPPCTRL), PUBLIC      :: icntrl = 0
    2728  REAL(DP), DIMENSION(NKPPCTRL), PUBLIC     :: rcntrl = 0.0_dp
     29  ! t_steps: fixed time steps in vector mode
    2830  REAL(DP), DIMENSION(NMAXFIXSTEPS), PUBLIC :: t_steps = 0.0_dp
    2931
  • palm/trunk/UTIL/chemistry/gasphase_preproc/kpp4palm/templates/module_header

    r3820 r3833  
    5656  !SAVE  ! NOTE: OCCURS AGAIN IN AUTOMATICALLY GENERATED CODE ...
    5757
    58 !  PUBLIC :: IERR_NAMES
     58! Public variables
     59  PUBLIC :: atol
     60  PUBLIC :: cs_mech
     61  PUBLIC :: eqn_names
     62  PUBLIC :: fakt
     63  PUBLIC :: nmaxfixsteps
     64  PUBLIC :: nphot
     65  PUBLIC :: nreact
     66  PUBLIC :: nspec
     67  PUBLIC :: nvar
     68  PUBLIC :: qvap
     69  PUBLIC :: phot
     70  PUBLIC :: phot_names
     71  PUBLIC :: rconst
     72  PUBLIC :: rtol
     73  PUBLIC :: spc_names
     74  PUBLIC :: temp
     75  PUBLIC :: vl_dim                     !< PUBLIC to enable other modules to distiguish between scalar and vec
    5976 
    60 ! PUBLIC :: SPC_NAMES, EQN_NAMES, EQN_TAGS, REQ_HET, REQ_AEROSOL, REQ_PHOTRAT &
    61 !         , REQ_MCFCT, IP_MAX, jname
    62 
    63   PUBLIC :: cs_mech
    64   PUBLIC :: eqn_names,  phot_names, spc_names
    65   PUBLIC :: nmaxfixsteps
    66   PUBLIC :: atol, rtol
    67   PUBLIC :: nspec, nreact
    68   PUBLIC :: temp
    69   PUBLIC :: qvap
    70   PUBLIC :: fakt
    71   PUBLIC :: phot
    72   PUBLIC :: rconst
    73   PUBLIC :: nvar
    74   PUBLIC :: nphot
    75   PUBLIC :: vl_dim                     ! Public to ebable other modules to distiguish between scalar and vec
    76  
    77   PUBLIC :: Initialize, Integrate, Update_rconst
     77! Public routines
    7878  PUBLIC :: chem_gasphase_integrate
     79  PUBLIC :: get_mechanism_name
     80  PUBLIC :: Initialize
    7981  PUBLIC :: initialize_kpp_ctrl
    80   PUBLIC :: get_mechanism_name
     82  PUBLIC :: Integrate
     83  PUBLIC :: Update_rconst
    8184
    8285! END OF MODULE HEADER TEMPLATE
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_cbm4/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:33 2019
     119! Time                 : Thu Mar 28 15:59:22 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    221224!
    222225! File                 : chem_gasphase_mod_Global.f90
    223 ! Time                 : Wed Mar 27 09:51:33 2019
     226! Time                 : Thu Mar 28 15:59:22 2019
    224227! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    225228! Equation file        : chem_gasphase_mod.kpp
     
    286289!
    287290! File                 : chem_gasphase_mod_JacobianSP.f90
    288 ! Time                 : Wed Mar 27 09:51:33 2019
     291! Time                 : Thu Mar 28 15:59:22 2019
    289292! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    290293! Equation file        : chem_gasphase_mod.kpp
     
    382385!
    383386! File                 : chem_gasphase_mod_Monitor.f90
    384 ! Time                 : Wed Mar 27 09:51:33 2019
     387! Time                 : Thu Mar 28 15:59:22 2019
    385388! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    386389! Equation file        : chem_gasphase_mod.kpp
     
    545548!
    546549! File                 : chem_gasphase_mod_Initialize.f90
    547 ! Time                 : Wed Mar 27 09:51:33 2019
     550! Time                 : Thu Mar 28 15:59:22 2019
    548551! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    549552! Equation file        : chem_gasphase_mod.kpp
     
    571574!
    572575! File                 : chem_gasphase_mod_Integrator.f90
    573 ! Time                 : Wed Mar 27 09:51:33 2019
     576! Time                 : Thu Mar 28 15:59:22 2019
    574577! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    575578! Equation file        : chem_gasphase_mod.kpp
     
    629632!
    630633! File                 : chem_gasphase_mod_LinearAlgebra.f90
    631 ! Time                 : Wed Mar 27 09:51:33 2019
     634! Time                 : Thu Mar 28 15:59:22 2019
    632635! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    633636! Equation file        : chem_gasphase_mod.kpp
     
    656659!
    657660! File                 : chem_gasphase_mod_Jacobian.f90
    658 ! Time                 : Wed Mar 27 09:51:33 2019
     661! Time                 : Thu Mar 28 15:59:22 2019
    659662! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    660663! Equation file        : chem_gasphase_mod.kpp
     
    683686!
    684687! File                 : chem_gasphase_mod_Function.f90
    685 ! Time                 : Wed Mar 27 09:51:33 2019
     688! Time                 : Thu Mar 28 15:59:22 2019
    686689! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    687690! Equation file        : chem_gasphase_mod.kpp
     
    712715!
    713716! File                 : chem_gasphase_mod_Rates.f90
    714 ! Time                 : Wed Mar 27 09:51:33 2019
     717! Time                 : Thu Mar 28 15:59:22 2019
    715718! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    716719! Equation file        : chem_gasphase_mod.kpp
     
    738741!
    739742! File                 : chem_gasphase_mod_Util.f90
    740 ! Time                 : Wed Mar 27 09:51:33 2019
     743! Time                 : Thu Mar 28 15:59:22 2019
    741744! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    742745! Equation file        : chem_gasphase_mod.kpp
     
    772775  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    773776  !
    774   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     777  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     778  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    775779  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     780  ! t_steps: fixed time steps in vector mode
    776781  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    777782
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_passive/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:34 2019
     119! Time                 : Thu Mar 28 15:59:23 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    189192!
    190193! File                 : chem_gasphase_mod_Global.f90
    191 ! Time                 : Wed Mar 27 09:51:34 2019
     194! Time                 : Thu Mar 28 15:59:23 2019
    192195! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    193196! Equation file        : chem_gasphase_mod.kpp
     
    254257!
    255258! File                 : chem_gasphase_mod_JacobianSP.f90
    256 ! Time                 : Wed Mar 27 09:51:34 2019
     259! Time                 : Thu Mar 28 15:59:23 2019
    257260! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    258261! Equation file        : chem_gasphase_mod.kpp
     
    298301!
    299302! File                 : chem_gasphase_mod_Monitor.f90
    300 ! Time                 : Wed Mar 27 09:51:34 2019
     303! Time                 : Thu Mar 28 15:59:23 2019
    301304! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    302305! Equation file        : chem_gasphase_mod.kpp
     
    358361!
    359362! File                 : chem_gasphase_mod_Initialize.f90
    360 ! Time                 : Wed Mar 27 09:51:34 2019
     363! Time                 : Thu Mar 28 15:59:23 2019
    361364! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    362365! Equation file        : chem_gasphase_mod.kpp
     
    384387!
    385388! File                 : chem_gasphase_mod_Integrator.f90
    386 ! Time                 : Wed Mar 27 09:51:34 2019
     389! Time                 : Thu Mar 28 15:59:23 2019
    387390! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    388391! Equation file        : chem_gasphase_mod.kpp
     
    442445!
    443446! File                 : chem_gasphase_mod_LinearAlgebra.f90
    444 ! Time                 : Wed Mar 27 09:51:34 2019
     447! Time                 : Thu Mar 28 15:59:23 2019
    445448! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    446449! Equation file        : chem_gasphase_mod.kpp
     
    469472!
    470473! File                 : chem_gasphase_mod_Jacobian.f90
    471 ! Time                 : Wed Mar 27 09:51:34 2019
     474! Time                 : Thu Mar 28 15:59:23 2019
    472475! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    473476! Equation file        : chem_gasphase_mod.kpp
     
    496499!
    497500! File                 : chem_gasphase_mod_Function.f90
    498 ! Time                 : Wed Mar 27 09:51:34 2019
     501! Time                 : Thu Mar 28 15:59:23 2019
    499502! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    500503! Equation file        : chem_gasphase_mod.kpp
     
    525528!
    526529! File                 : chem_gasphase_mod_Rates.f90
    527 ! Time                 : Wed Mar 27 09:51:34 2019
     530! Time                 : Thu Mar 28 15:59:23 2019
    528531! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    529532! Equation file        : chem_gasphase_mod.kpp
     
    551554!
    552555! File                 : chem_gasphase_mod_Util.f90
    553 ! Time                 : Wed Mar 27 09:51:34 2019
     556! Time                 : Thu Mar 28 15:59:23 2019
    554557! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    555558! Equation file        : chem_gasphase_mod.kpp
     
    585588  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    586589  !
    587   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     590  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     591  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    588592  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     593  ! t_steps: fixed time steps in vector mode
    589594  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    590595
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_passive1/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:34 2019
     119! Time                 : Thu Mar 28 15:59:24 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    188191!
    189192! File                 : chem_gasphase_mod_Global.f90
    190 ! Time                 : Wed Mar 27 09:51:34 2019
     193! Time                 : Thu Mar 28 15:59:24 2019
    191194! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    192195! Equation file        : chem_gasphase_mod.kpp
     
    253256!
    254257! File                 : chem_gasphase_mod_JacobianSP.f90
    255 ! Time                 : Wed Mar 27 09:51:34 2019
     258! Time                 : Thu Mar 28 15:59:24 2019
    256259! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    257260! Equation file        : chem_gasphase_mod.kpp
     
    297300!
    298301! File                 : chem_gasphase_mod_Monitor.f90
    299 ! Time                 : Wed Mar 27 09:51:34 2019
     302! Time                 : Thu Mar 28 15:59:24 2019
    300303! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    301304! Equation file        : chem_gasphase_mod.kpp
     
    356359!
    357360! File                 : chem_gasphase_mod_Initialize.f90
    358 ! Time                 : Wed Mar 27 09:51:34 2019
     361! Time                 : Thu Mar 28 15:59:24 2019
    359362! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    360363! Equation file        : chem_gasphase_mod.kpp
     
    382385!
    383386! File                 : chem_gasphase_mod_Integrator.f90
    384 ! Time                 : Wed Mar 27 09:51:34 2019
     387! Time                 : Thu Mar 28 15:59:24 2019
    385388! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    386389! Equation file        : chem_gasphase_mod.kpp
     
    440443!
    441444! File                 : chem_gasphase_mod_LinearAlgebra.f90
    442 ! Time                 : Wed Mar 27 09:51:34 2019
     445! Time                 : Thu Mar 28 15:59:24 2019
    443446! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    444447! Equation file        : chem_gasphase_mod.kpp
     
    467470!
    468471! File                 : chem_gasphase_mod_Jacobian.f90
    469 ! Time                 : Wed Mar 27 09:51:34 2019
     472! Time                 : Thu Mar 28 15:59:24 2019
    470473! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    471474! Equation file        : chem_gasphase_mod.kpp
     
    494497!
    495498! File                 : chem_gasphase_mod_Function.f90
    496 ! Time                 : Wed Mar 27 09:51:34 2019
     499! Time                 : Thu Mar 28 15:59:24 2019
    497500! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    498501! Equation file        : chem_gasphase_mod.kpp
     
    523526!
    524527! File                 : chem_gasphase_mod_Rates.f90
    525 ! Time                 : Wed Mar 27 09:51:34 2019
     528! Time                 : Thu Mar 28 15:59:24 2019
    526529! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    527530! Equation file        : chem_gasphase_mod.kpp
     
    549552!
    550553! File                 : chem_gasphase_mod_Util.f90
    551 ! Time                 : Wed Mar 27 09:51:34 2019
     554! Time                 : Thu Mar 28 15:59:24 2019
    552555! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    553556! Equation file        : chem_gasphase_mod.kpp
     
    583586  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    584587  !
    585   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     588  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     589  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    586590  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     591  ! t_steps: fixed time steps in vector mode
    587592  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    588593
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_phstat/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:35 2019
     119! Time                 : Thu Mar 28 15:59:25 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    190193!
    191194! File                 : chem_gasphase_mod_Global.f90
    192 ! Time                 : Wed Mar 27 09:51:35 2019
     195! Time                 : Thu Mar 28 15:59:25 2019
    193196! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    194197! Equation file        : chem_gasphase_mod.kpp
     
    255258!
    256259! File                 : chem_gasphase_mod_JacobianSP.f90
    257 ! Time                 : Wed Mar 27 09:51:35 2019
     260! Time                 : Thu Mar 28 15:59:25 2019
    258261! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    259262! Equation file        : chem_gasphase_mod.kpp
     
    299302!
    300303! File                 : chem_gasphase_mod_Monitor.f90
    301 ! Time                 : Wed Mar 27 09:51:35 2019
     304! Time                 : Thu Mar 28 15:59:25 2019
    302305! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    303306! Equation file        : chem_gasphase_mod.kpp
     
    359362!
    360363! File                 : chem_gasphase_mod_Initialize.f90
    361 ! Time                 : Wed Mar 27 09:51:35 2019
     364! Time                 : Thu Mar 28 15:59:25 2019
    362365! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    363366! Equation file        : chem_gasphase_mod.kpp
     
    385388!
    386389! File                 : chem_gasphase_mod_Integrator.f90
    387 ! Time                 : Wed Mar 27 09:51:35 2019
     390! Time                 : Thu Mar 28 15:59:25 2019
    388391! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    389392! Equation file        : chem_gasphase_mod.kpp
     
    443446!
    444447! File                 : chem_gasphase_mod_LinearAlgebra.f90
    445 ! Time                 : Wed Mar 27 09:51:35 2019
     448! Time                 : Thu Mar 28 15:59:25 2019
    446449! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    447450! Equation file        : chem_gasphase_mod.kpp
     
    470473!
    471474! File                 : chem_gasphase_mod_Jacobian.f90
    472 ! Time                 : Wed Mar 27 09:51:35 2019
     475! Time                 : Thu Mar 28 15:59:25 2019
    473476! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    474477! Equation file        : chem_gasphase_mod.kpp
     
    497500!
    498501! File                 : chem_gasphase_mod_Function.f90
    499 ! Time                 : Wed Mar 27 09:51:35 2019
     502! Time                 : Thu Mar 28 15:59:25 2019
    500503! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    501504! Equation file        : chem_gasphase_mod.kpp
     
    526529!
    527530! File                 : chem_gasphase_mod_Rates.f90
    528 ! Time                 : Wed Mar 27 09:51:35 2019
     531! Time                 : Thu Mar 28 15:59:25 2019
    529532! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    530533! Equation file        : chem_gasphase_mod.kpp
     
    552555!
    553556! File                 : chem_gasphase_mod_Util.f90
    554 ! Time                 : Wed Mar 27 09:51:35 2019
     557! Time                 : Thu Mar 28 15:59:25 2019
    555558! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    556559! Equation file        : chem_gasphase_mod.kpp
     
    586589  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    587590  !
    588   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     591  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     592  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    589593  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     594  ! t_steps: fixed time steps in vector mode
    590595  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    591596
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_phstatp/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:40 2019
     119! Time                 : Thu Mar 28 15:59:30 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    191194!
    192195! File                 : chem_gasphase_mod_Global.f90
    193 ! Time                 : Wed Mar 27 09:51:40 2019
     196! Time                 : Thu Mar 28 15:59:30 2019
    194197! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    195198! Equation file        : chem_gasphase_mod.kpp
     
    256259!
    257260! File                 : chem_gasphase_mod_JacobianSP.f90
    258 ! Time                 : Wed Mar 27 09:51:40 2019
     261! Time                 : Thu Mar 28 15:59:30 2019
    259262! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    260263! Equation file        : chem_gasphase_mod.kpp
     
    300303!
    301304! File                 : chem_gasphase_mod_Monitor.f90
    302 ! Time                 : Wed Mar 27 09:51:40 2019
     305! Time                 : Thu Mar 28 15:59:30 2019
    303306! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    304307! Equation file        : chem_gasphase_mod.kpp
     
    362365!
    363366! File                 : chem_gasphase_mod_Initialize.f90
    364 ! Time                 : Wed Mar 27 09:51:40 2019
     367! Time                 : Thu Mar 28 15:59:30 2019
    365368! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    366369! Equation file        : chem_gasphase_mod.kpp
     
    388391!
    389392! File                 : chem_gasphase_mod_Integrator.f90
    390 ! Time                 : Wed Mar 27 09:51:40 2019
     393! Time                 : Thu Mar 28 15:59:30 2019
    391394! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    392395! Equation file        : chem_gasphase_mod.kpp
     
    446449!
    447450! File                 : chem_gasphase_mod_LinearAlgebra.f90
    448 ! Time                 : Wed Mar 27 09:51:40 2019
     451! Time                 : Thu Mar 28 15:59:30 2019
    449452! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    450453! Equation file        : chem_gasphase_mod.kpp
     
    473476!
    474477! File                 : chem_gasphase_mod_Jacobian.f90
    475 ! Time                 : Wed Mar 27 09:51:40 2019
     478! Time                 : Thu Mar 28 15:59:30 2019
    476479! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    477480! Equation file        : chem_gasphase_mod.kpp
     
    500503!
    501504! File                 : chem_gasphase_mod_Function.f90
    502 ! Time                 : Wed Mar 27 09:51:40 2019
     505! Time                 : Thu Mar 28 15:59:30 2019
    503506! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    504507! Equation file        : chem_gasphase_mod.kpp
     
    529532!
    530533! File                 : chem_gasphase_mod_Rates.f90
    531 ! Time                 : Wed Mar 27 09:51:40 2019
     534! Time                 : Thu Mar 28 15:59:30 2019
    532535! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    533536! Equation file        : chem_gasphase_mod.kpp
     
    555558!
    556559! File                 : chem_gasphase_mod_Util.f90
    557 ! Time                 : Wed Mar 27 09:51:40 2019
     560! Time                 : Thu Mar 28 15:59:30 2019
    558561! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    559562! Equation file        : chem_gasphase_mod.kpp
     
    589592  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    590593  !
    591   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     594  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     595  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    592596  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     597  ! t_steps: fixed time steps in vector mode
    593598  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    594599
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_salsa+phstat/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:37 2019
     119! Time                 : Thu Mar 28 15:59:27 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    190193!
    191194! File                 : chem_gasphase_mod_Global.f90
    192 ! Time                 : Wed Mar 27 09:51:37 2019
     195! Time                 : Thu Mar 28 15:59:27 2019
    193196! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    194197! Equation file        : chem_gasphase_mod.kpp
     
    264267!
    265268! File                 : chem_gasphase_mod_JacobianSP.f90
    266 ! Time                 : Wed Mar 27 09:51:37 2019
     269! Time                 : Thu Mar 28 15:59:27 2019
    267270! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    268271! Equation file        : chem_gasphase_mod.kpp
     
    308311!
    309312! File                 : chem_gasphase_mod_Monitor.f90
    310 ! Time                 : Wed Mar 27 09:51:37 2019
     313! Time                 : Thu Mar 28 15:59:27 2019
    311314! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    312315! Equation file        : chem_gasphase_mod.kpp
     
    368371!
    369372! File                 : chem_gasphase_mod_Initialize.f90
    370 ! Time                 : Wed Mar 27 09:51:37 2019
     373! Time                 : Thu Mar 28 15:59:27 2019
    371374! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    372375! Equation file        : chem_gasphase_mod.kpp
     
    394397!
    395398! File                 : chem_gasphase_mod_Integrator.f90
    396 ! Time                 : Wed Mar 27 09:51:37 2019
     399! Time                 : Thu Mar 28 15:59:27 2019
    397400! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    398401! Equation file        : chem_gasphase_mod.kpp
     
    452455!
    453456! File                 : chem_gasphase_mod_LinearAlgebra.f90
    454 ! Time                 : Wed Mar 27 09:51:37 2019
     457! Time                 : Thu Mar 28 15:59:27 2019
    455458! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    456459! Equation file        : chem_gasphase_mod.kpp
     
    479482!
    480483! File                 : chem_gasphase_mod_Jacobian.f90
    481 ! Time                 : Wed Mar 27 09:51:37 2019
     484! Time                 : Thu Mar 28 15:59:27 2019
    482485! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    483486! Equation file        : chem_gasphase_mod.kpp
     
    506509!
    507510! File                 : chem_gasphase_mod_Function.f90
    508 ! Time                 : Wed Mar 27 09:51:37 2019
     511! Time                 : Thu Mar 28 15:59:27 2019
    509512! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    510513! Equation file        : chem_gasphase_mod.kpp
     
    535538!
    536539! File                 : chem_gasphase_mod_Rates.f90
    537 ! Time                 : Wed Mar 27 09:51:37 2019
     540! Time                 : Thu Mar 28 15:59:27 2019
    538541! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    539542! Equation file        : chem_gasphase_mod.kpp
     
    561564!
    562565! File                 : chem_gasphase_mod_Util.f90
    563 ! Time                 : Wed Mar 27 09:51:37 2019
     566! Time                 : Thu Mar 28 15:59:27 2019
    564567! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    565568! Equation file        : chem_gasphase_mod.kpp
     
    595598  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    596599  !
    597   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     600  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     601  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    598602  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     603  ! t_steps: fixed time steps in vector mode
    599604  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    600605
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_salsa+simple/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:38 2019
     119! Time                 : Thu Mar 28 15:59:27 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    202205!
    203206! File                 : chem_gasphase_mod_Global.f90
    204 ! Time                 : Wed Mar 27 09:51:38 2019
     207! Time                 : Thu Mar 28 15:59:27 2019
    205208! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    206209! Equation file        : chem_gasphase_mod.kpp
     
    273276!
    274277! File                 : chem_gasphase_mod_JacobianSP.f90
    275 ! Time                 : Wed Mar 27 09:51:38 2019
     278! Time                 : Thu Mar 28 15:59:27 2019
    276279! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    277280! Equation file        : chem_gasphase_mod.kpp
     
    325328!
    326329! File                 : chem_gasphase_mod_Monitor.f90
    327 ! Time                 : Wed Mar 27 09:51:38 2019
     330! Time                 : Thu Mar 28 15:59:27 2019
    328331! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    329332! Equation file        : chem_gasphase_mod.kpp
     
    399402!
    400403! File                 : chem_gasphase_mod_Initialize.f90
    401 ! Time                 : Wed Mar 27 09:51:38 2019
     404! Time                 : Thu Mar 28 15:59:27 2019
    402405! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    403406! Equation file        : chem_gasphase_mod.kpp
     
    425428!
    426429! File                 : chem_gasphase_mod_Integrator.f90
    427 ! Time                 : Wed Mar 27 09:51:38 2019
     430! Time                 : Thu Mar 28 15:59:27 2019
    428431! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    429432! Equation file        : chem_gasphase_mod.kpp
     
    483486!
    484487! File                 : chem_gasphase_mod_LinearAlgebra.f90
    485 ! Time                 : Wed Mar 27 09:51:38 2019
     488! Time                 : Thu Mar 28 15:59:27 2019
    486489! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    487490! Equation file        : chem_gasphase_mod.kpp
     
    510513!
    511514! File                 : chem_gasphase_mod_Jacobian.f90
    512 ! Time                 : Wed Mar 27 09:51:38 2019
     515! Time                 : Thu Mar 28 15:59:27 2019
    513516! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    514517! Equation file        : chem_gasphase_mod.kpp
     
    537540!
    538541! File                 : chem_gasphase_mod_Function.f90
    539 ! Time                 : Wed Mar 27 09:51:38 2019
     542! Time                 : Thu Mar 28 15:59:27 2019
    540543! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    541544! Equation file        : chem_gasphase_mod.kpp
     
    566569!
    567570! File                 : chem_gasphase_mod_Rates.f90
    568 ! Time                 : Wed Mar 27 09:51:38 2019
     571! Time                 : Thu Mar 28 15:59:27 2019
    569572! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    570573! Equation file        : chem_gasphase_mod.kpp
     
    592595!
    593596! File                 : chem_gasphase_mod_Util.f90
    594 ! Time                 : Wed Mar 27 09:51:38 2019
     597! Time                 : Thu Mar 28 15:59:27 2019
    595598! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    596599! Equation file        : chem_gasphase_mod.kpp
     
    626629  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    627630  !
    628   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     631  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     632  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    629633  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     634  ! t_steps: fixed time steps in vector mode
    630635  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    631636
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_salsagas/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:36 2019
     119! Time                 : Thu Mar 28 15:59:26 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    192195!
    193196! File                 : chem_gasphase_mod_Global.f90
    194 ! Time                 : Wed Mar 27 09:51:36 2019
     197! Time                 : Thu Mar 28 15:59:26 2019
    195198! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    196199! Equation file        : chem_gasphase_mod.kpp
     
    259262!
    260263! File                 : chem_gasphase_mod_JacobianSP.f90
    261 ! Time                 : Wed Mar 27 09:51:36 2019
     264! Time                 : Thu Mar 28 15:59:26 2019
    262265! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    263266! Equation file        : chem_gasphase_mod.kpp
     
    303306!
    304307! File                 : chem_gasphase_mod_Monitor.f90
    305 ! Time                 : Wed Mar 27 09:51:36 2019
     308! Time                 : Thu Mar 28 15:59:26 2019
    306309! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    307310! Equation file        : chem_gasphase_mod.kpp
     
    367370!
    368371! File                 : chem_gasphase_mod_Initialize.f90
    369 ! Time                 : Wed Mar 27 09:51:36 2019
     372! Time                 : Thu Mar 28 15:59:26 2019
    370373! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    371374! Equation file        : chem_gasphase_mod.kpp
     
    393396!
    394397! File                 : chem_gasphase_mod_Integrator.f90
    395 ! Time                 : Wed Mar 27 09:51:36 2019
     398! Time                 : Thu Mar 28 15:59:26 2019
    396399! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    397400! Equation file        : chem_gasphase_mod.kpp
     
    451454!
    452455! File                 : chem_gasphase_mod_LinearAlgebra.f90
    453 ! Time                 : Wed Mar 27 09:51:36 2019
     456! Time                 : Thu Mar 28 15:59:26 2019
    454457! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    455458! Equation file        : chem_gasphase_mod.kpp
     
    478481!
    479482! File                 : chem_gasphase_mod_Jacobian.f90
    480 ! Time                 : Wed Mar 27 09:51:36 2019
     483! Time                 : Thu Mar 28 15:59:26 2019
    481484! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    482485! Equation file        : chem_gasphase_mod.kpp
     
    505508!
    506509! File                 : chem_gasphase_mod_Function.f90
    507 ! Time                 : Wed Mar 27 09:51:36 2019
     510! Time                 : Thu Mar 28 15:59:26 2019
    508511! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    509512! Equation file        : chem_gasphase_mod.kpp
     
    534537!
    535538! File                 : chem_gasphase_mod_Rates.f90
    536 ! Time                 : Wed Mar 27 09:51:36 2019
     539! Time                 : Thu Mar 28 15:59:26 2019
    537540! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    538541! Equation file        : chem_gasphase_mod.kpp
     
    560563!
    561564! File                 : chem_gasphase_mod_Util.f90
    562 ! Time                 : Wed Mar 27 09:51:36 2019
     565! Time                 : Thu Mar 28 15:59:26 2019
    563566! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    564567! Equation file        : chem_gasphase_mod.kpp
     
    594597  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    595598  !
    596   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     599  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     600  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    597601  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     602  ! t_steps: fixed time steps in vector mode
    598603  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    599604
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_simple/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:38 2019
     119! Time                 : Thu Mar 28 15:59:28 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    198201!
    199202! File                 : chem_gasphase_mod_Global.f90
    200 ! Time                 : Wed Mar 27 09:51:38 2019
     203! Time                 : Thu Mar 28 15:59:28 2019
    201204! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    202205! Equation file        : chem_gasphase_mod.kpp
     
    263266!
    264267! File                 : chem_gasphase_mod_JacobianSP.f90
    265 ! Time                 : Wed Mar 27 09:51:38 2019
     268! Time                 : Thu Mar 28 15:59:28 2019
    266269! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    267270! Equation file        : chem_gasphase_mod.kpp
     
    313316!
    314317! File                 : chem_gasphase_mod_Monitor.f90
    315 ! Time                 : Wed Mar 27 09:51:38 2019
     318! Time                 : Thu Mar 28 15:59:28 2019
    316319! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    317320! Equation file        : chem_gasphase_mod.kpp
     
    382385!
    383386! File                 : chem_gasphase_mod_Initialize.f90
    384 ! Time                 : Wed Mar 27 09:51:38 2019
     387! Time                 : Thu Mar 28 15:59:28 2019
    385388! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    386389! Equation file        : chem_gasphase_mod.kpp
     
    408411!
    409412! File                 : chem_gasphase_mod_Integrator.f90
    410 ! Time                 : Wed Mar 27 09:51:38 2019
     413! Time                 : Thu Mar 28 15:59:28 2019
    411414! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    412415! Equation file        : chem_gasphase_mod.kpp
     
    466469!
    467470! File                 : chem_gasphase_mod_LinearAlgebra.f90
    468 ! Time                 : Wed Mar 27 09:51:38 2019
     471! Time                 : Thu Mar 28 15:59:28 2019
    469472! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    470473! Equation file        : chem_gasphase_mod.kpp
     
    493496!
    494497! File                 : chem_gasphase_mod_Jacobian.f90
    495 ! Time                 : Wed Mar 27 09:51:38 2019
     498! Time                 : Thu Mar 28 15:59:28 2019
    496499! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    497500! Equation file        : chem_gasphase_mod.kpp
     
    520523!
    521524! File                 : chem_gasphase_mod_Function.f90
    522 ! Time                 : Wed Mar 27 09:51:38 2019
     525! Time                 : Thu Mar 28 15:59:28 2019
    523526! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    524527! Equation file        : chem_gasphase_mod.kpp
     
    549552!
    550553! File                 : chem_gasphase_mod_Rates.f90
    551 ! Time                 : Wed Mar 27 09:51:38 2019
     554! Time                 : Thu Mar 28 15:59:28 2019
    552555! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    553556! Equation file        : chem_gasphase_mod.kpp
     
    575578!
    576579! File                 : chem_gasphase_mod_Util.f90
    577 ! Time                 : Wed Mar 27 09:51:38 2019
     580! Time                 : Thu Mar 28 15:59:28 2019
    578581! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    579582! Equation file        : chem_gasphase_mod.kpp
     
    609612  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    610613  !
    611   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     614  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     615  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    612616  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     617  ! t_steps: fixed time steps in vector mode
    613618  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    614619
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_simplep/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:39 2019
     119! Time                 : Thu Mar 28 15:59:29 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    199202!
    200203! File                 : chem_gasphase_mod_Global.f90
    201 ! Time                 : Wed Mar 27 09:51:39 2019
     204! Time                 : Thu Mar 28 15:59:29 2019
    202205! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    203206! Equation file        : chem_gasphase_mod.kpp
     
    264267!
    265268! File                 : chem_gasphase_mod_JacobianSP.f90
    266 ! Time                 : Wed Mar 27 09:51:39 2019
     269! Time                 : Thu Mar 28 15:59:29 2019
    267270! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    268271! Equation file        : chem_gasphase_mod.kpp
     
    314317!
    315318! File                 : chem_gasphase_mod_Monitor.f90
    316 ! Time                 : Wed Mar 27 09:51:39 2019
     319! Time                 : Thu Mar 28 15:59:29 2019
    317320! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    318321! Equation file        : chem_gasphase_mod.kpp
     
    384387!
    385388! File                 : chem_gasphase_mod_Initialize.f90
    386 ! Time                 : Wed Mar 27 09:51:39 2019
     389! Time                 : Thu Mar 28 15:59:29 2019
    387390! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    388391! Equation file        : chem_gasphase_mod.kpp
     
    410413!
    411414! File                 : chem_gasphase_mod_Integrator.f90
    412 ! Time                 : Wed Mar 27 09:51:39 2019
     415! Time                 : Thu Mar 28 15:59:29 2019
    413416! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    414417! Equation file        : chem_gasphase_mod.kpp
     
    468471!
    469472! File                 : chem_gasphase_mod_LinearAlgebra.f90
    470 ! Time                 : Wed Mar 27 09:51:39 2019
     473! Time                 : Thu Mar 28 15:59:29 2019
    471474! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    472475! Equation file        : chem_gasphase_mod.kpp
     
    495498!
    496499! File                 : chem_gasphase_mod_Jacobian.f90
    497 ! Time                 : Wed Mar 27 09:51:39 2019
     500! Time                 : Thu Mar 28 15:59:29 2019
    498501! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    499502! Equation file        : chem_gasphase_mod.kpp
     
    522525!
    523526! File                 : chem_gasphase_mod_Function.f90
    524 ! Time                 : Wed Mar 27 09:51:39 2019
     527! Time                 : Thu Mar 28 15:59:29 2019
    525528! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    526529! Equation file        : chem_gasphase_mod.kpp
     
    551554!
    552555! File                 : chem_gasphase_mod_Rates.f90
    553 ! Time                 : Wed Mar 27 09:51:39 2019
     556! Time                 : Thu Mar 28 15:59:29 2019
    554557! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    555558! Equation file        : chem_gasphase_mod.kpp
     
    577580!
    578581! File                 : chem_gasphase_mod_Util.f90
    579 ! Time                 : Wed Mar 27 09:51:39 2019
     582! Time                 : Thu Mar 28 15:59:29 2019
    580583! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    581584! Equation file        : chem_gasphase_mod.kpp
     
    611614  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    612615  !
    613   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     616  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     617  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    614618  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     619  ! t_steps: fixed time steps in vector mode
    615620  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    616621
  • palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_smog/chem_gasphase_mod.f90

    r3820 r3833  
    6060  !SAVE  ! note: occurs again in automatically generated code ...
    6161
    62 !  PUBLIC :: IERR_NAMES
    63  
    64 ! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
    65 !         ,REQ_MCFCT,IP_MAX,jname
    66 
     62! Public variables
     63  PUBLIC :: atol
    6764  PUBLIC :: cs_mech
    68   PUBLIC :: eqn_names, phot_names, spc_names
     65  PUBLIC :: eqn_names
     66  PUBLIC :: fakt
    6967  PUBLIC :: nmaxfixsteps
    70   PUBLIC :: atol, rtol
    71   PUBLIC :: nspec, nreact
     68  PUBLIC :: nphot
     69  PUBLIC :: nreact
     70  PUBLIC :: nspec
     71  PUBLIC :: nvar
     72  PUBLIC :: qvap
     73  PUBLIC :: phot
     74  PUBLIC :: phot_names
     75  PUBLIC :: rconst
     76  PUBLIC :: rtol
     77  PUBLIC :: spc_names
    7278  PUBLIC :: temp
    73   PUBLIC :: qvap
    74   PUBLIC :: fakt
    75   PUBLIC :: phot
    76   PUBLIC :: rconst
    77   PUBLIC :: nvar
    78   PUBLIC :: nphot
    79   PUBLIC :: vl_dim                     ! PUBLIC to ebable other MODULEs to distiguish between scalar and vec
    80  
    81   PUBLIC :: initialize, integrate, update_rconst
     79  PUBLIC :: vl_dim                     !< PUBLIC to enable other MODULEs to distiguish between scalar and vec
     80 
     81! Public routines
    8282  PUBLIC :: chem_gasphase_integrate
     83  PUBLIC :: get_mechanism_name
     84  PUBLIC :: initialize
    8385  PUBLIC :: initialize_kpp_ctrl
    84   PUBLIC :: get_mechanism_name
     86  PUBLIC :: integrate
     87  PUBLIC :: update_rconst
    8588
    8689! END OF MODULE HEADER TEMPLATE
     
    114117!
    115118! File                 : chem_gasphase_mod_Parameters.f90
    116 ! Time                 : Wed Mar 27 09:51:40 2019
     119! Time                 : Thu Mar 28 15:59:29 2019
    117120! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    118121! Equation file        : chem_gasphase_mod.kpp
     
    206209!
    207210! File                 : chem_gasphase_mod_Global.f90
    208 ! Time                 : Wed Mar 27 09:51:40 2019
     211! Time                 : Thu Mar 28 15:59:29 2019
    209212! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    210213! Equation file        : chem_gasphase_mod.kpp
     
    271274!
    272275! File                 : chem_gasphase_mod_JacobianSP.f90
    273 ! Time                 : Wed Mar 27 09:51:40 2019
     276! Time                 : Thu Mar 28 15:59:29 2019
    274277! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    275278! Equation file        : chem_gasphase_mod.kpp
     
    327330!
    328331! File                 : chem_gasphase_mod_Monitor.f90
    329 ! Time                 : Wed Mar 27 09:51:40 2019
     332! Time                 : Thu Mar 28 15:59:29 2019
    330333! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    331334! Equation file        : chem_gasphase_mod.kpp
     
    403406!
    404407! File                 : chem_gasphase_mod_Initialize.f90
    405 ! Time                 : Wed Mar 27 09:51:40 2019
     408! Time                 : Thu Mar 28 15:59:29 2019
    406409! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    407410! Equation file        : chem_gasphase_mod.kpp
     
    429432!
    430433! File                 : chem_gasphase_mod_Integrator.f90
    431 ! Time                 : Wed Mar 27 09:51:40 2019
     434! Time                 : Thu Mar 28 15:59:29 2019
    432435! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    433436! Equation file        : chem_gasphase_mod.kpp
     
    487490!
    488491! File                 : chem_gasphase_mod_LinearAlgebra.f90
    489 ! Time                 : Wed Mar 27 09:51:40 2019
     492! Time                 : Thu Mar 28 15:59:29 2019
    490493! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    491494! Equation file        : chem_gasphase_mod.kpp
     
    514517!
    515518! File                 : chem_gasphase_mod_Jacobian.f90
    516 ! Time                 : Wed Mar 27 09:51:40 2019
     519! Time                 : Thu Mar 28 15:59:29 2019
    517520! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    518521! Equation file        : chem_gasphase_mod.kpp
     
    541544!
    542545! File                 : chem_gasphase_mod_Function.f90
    543 ! Time                 : Wed Mar 27 09:51:40 2019
     546! Time                 : Thu Mar 28 15:59:29 2019
    544547! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    545548! Equation file        : chem_gasphase_mod.kpp
     
    570573!
    571574! File                 : chem_gasphase_mod_Rates.f90
    572 ! Time                 : Wed Mar 27 09:51:40 2019
     575! Time                 : Thu Mar 28 15:59:29 2019
    573576! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    574577! Equation file        : chem_gasphase_mod.kpp
     
    596599!
    597600! File                 : chem_gasphase_mod_Util.f90
    598 ! Time                 : Wed Mar 27 09:51:40 2019
     601! Time                 : Thu Mar 28 15:59:29 2019
    599602! Working directory    : /home/forkel-r/palmstuff/work/trunk20190327/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm
    600603! Equation file        : chem_gasphase_mod.kpp
     
    630633  INTEGER, PARAMETER, PUBLIC :: nkppctrl = 20
    631634  !
    632   INTEGER, DIMENSION(nkppctrl), PUBLIC     :: icntrl = 0
     635  ! steering PARAMETERs for chemistry solver (see kpp domumentation)
     636  INTEGER, DIMENSION(nkppctrl), PUBLIC      :: icntrl = 0
    633637  REAL(dp), DIMENSION(nkppctrl), PUBLIC     :: rcntrl = 0.0_dp
     638  ! t_steps: fixed time steps in vector mode
    634639  REAL(dp), DIMENSION(nmaxfixsteps), PUBLIC :: t_steps = 0.0_dp
    635640
Note: See TracChangeset for help on using the changeset viewer.