Ignore:
Timestamp:
Sep 11, 2019 1:58:14 PM (5 years ago)
Author:
suehring
Message:

Several bugfixes: profile initialization of chemical species in restart runs; Runge-Kutta tendency array not initialized in chemistry model in restart runs; fixed determination of time indices for chemical emissions (introduced with commit -4227); Update chemistry profiles in offline nesting; initialize canopy resistances for greened building walls (even if green fraction is zero)

File:
1 edited

Legend:

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

    r4227 r4230  
    2727! -----------------
    2828! $Id$
     29! Bugfix, initialize mean profiles also in restart runs. Also initialize
     30! array used for Runge-Kutta tendecies in restart runs. 
     31!
     32! 4227 2019-09-10 18:04:34Z gronemeier
    2933! implement new palm_date_time_mod
    3034!
     
    19481952          ENDDO
    19491953       ENDIF
    1950 !
    1951 !--    Initiale old and new time levels.
    1952        DO  lsp = 1, nvar
    1953           chem_species(lsp)%tconc_m = 0.0_wp                     
    1954           chem_species(lsp)%conc_p  = chem_species(lsp)%conc     
    1955        ENDDO
    19561954
    19571955    ENDIF
     1956!
     1957!-- Initiale old and new time levels. Note, this has to be done also in restart runs
     1958    DO  lsp = 1, nvar
     1959       chem_species(lsp)%tconc_m = 0.0_wp                     
     1960       chem_species(lsp)%conc_p  = chem_species(lsp)%conc     
     1961    ENDDO
    19581962
    19591963    DO  lsp = 1, nphot
     
    19641968!--          WRITE(6,'(a,i4,3x,a)')  'Photolysis: ',lsp,TRIM( phot_names(lsp) )
    19651969!--       ENDIF
    1966           phot_frequen(lsp)%freq(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  =>  freq_1(:,:,:,lsp)
     1970       phot_frequen(lsp)%freq(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  =>  freq_1(:,:,:,lsp)
    19671971    ENDDO
    19681972
     
    19821986!------------------------------------------------------------------------------!
    19831987 SUBROUTINE chem_init_profiles             
    1984 !
    1985 !-- SUBROUTINE is called from chem_init in case of TRIM( initializing_actions ) /= 'read_restart_data'
    1986 !< We still need to see what has to be done in case of restart run
    19871988
    19881989    USE chem_modules
     
    20002001!-- "cs_heights" are prescribed, their values will!override the constant profile given by
    20012002!-- "cs_surface".
    2002     IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
    2003        lsp_usr = 1
    2004        DO  WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )   !'novalue' is the default
    2005           DO  lsp = 1, nspec                                !
    2006 !
    2007 !--          create initial profile (conc_pr_init) for each chemical species
    2008              IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN   !
    2009                 IF ( cs_profile(lsp_usr,1) == 9999999.9_wp )  THEN
    2010 !
    2011 !--               set a vertically constant profile based on the surface conc (cs_surface(lsp_usr)) of each species
    2012                    DO lpr_lev = 0, nzt+1
    2013                       chem_species(lsp)%conc_pr_init(lpr_lev) = cs_surface(lsp_usr)
    2014                    ENDDO
    2015                 ELSE
    2016                    IF ( cs_heights(1,1) /= 0.0_wp )  THEN
    2017                       message_string = 'The surface value of cs_heights must be 0.0'
    2018                       CALL message( 'chem_check_parameters', 'CM0434', 1, 2, 0, 6, 0 )
     2003!     IF ( TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
     2004    lsp_usr = 1
     2005    DO  WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )   !'novalue' is the default
     2006       DO  lsp = 1, nspec                                !
     2007!
     2008!--       create initial profile (conc_pr_init) for each chemical species
     2009          IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN   !
     2010             IF ( cs_profile(lsp_usr,1) == 9999999.9_wp )  THEN
     2011!
     2012!--            set a vertically constant profile based on the surface conc (cs_surface(lsp_usr)) of each species
     2013                DO lpr_lev = 0, nzt+1
     2014                   chem_species(lsp)%conc_pr_init(lpr_lev) = cs_surface(lsp_usr)
     2015                ENDDO
     2016             ELSE
     2017                IF ( cs_heights(1,1) /= 0.0_wp )  THEN
     2018                   message_string = 'The surface value of cs_heights must be 0.0'
     2019                   CALL message( 'chem_check_parameters', 'CM0434', 1, 2, 0, 6, 0 )
     2020                ENDIF
     2021
     2022                use_prescribed_profile_data = .TRUE.
     2023
     2024                npr_lev = 1
     2025!                chem_species(lsp)%conc_pr_init(0) = 0.0_wp
     2026                DO  lpr_lev = 1, nz+1
     2027                   IF ( npr_lev < 100 )  THEN
     2028                      DO  WHILE ( cs_heights(lsp_usr, npr_lev+1) <= zu(lpr_lev) )
     2029                         npr_lev = npr_lev + 1
     2030                         IF ( npr_lev == 100 )  THEN
     2031                            message_string = 'number of chem spcs exceeding the limit'
     2032                            CALL message( 'chem_check_parameters', 'CM0435', 1, 2, 0, 6, 0 )               
     2033                            EXIT
     2034                         ENDIF
     2035                      ENDDO
    20192036                   ENDIF
    2020 
    2021                    use_prescribed_profile_data = .TRUE.
    2022 
    2023                    npr_lev = 1
    2024 !                   chem_species(lsp)%conc_pr_init(0) = 0.0_wp
    2025                    DO  lpr_lev = 1, nz+1
    2026                       IF ( npr_lev < 100 )  THEN
    2027                          DO  WHILE ( cs_heights(lsp_usr, npr_lev+1) <= zu(lpr_lev) )
    2028                             npr_lev = npr_lev + 1
    2029                             IF ( npr_lev == 100 )  THEN
    2030                                message_string = 'number of chem spcs exceeding the limit'
    2031                                CALL message( 'chem_check_parameters', 'CM0435', 1, 2, 0, 6, 0 )               
    2032                                EXIT
    2033                             ENDIF
    2034                          ENDDO
    2035                       ENDIF
    2036                       IF ( npr_lev < 100  .AND.  cs_heights(lsp_usr,npr_lev+1) /= 9999999.9_wp )  THEN
    2037                          chem_species(lsp)%conc_pr_init(lpr_lev) = cs_profile(lsp_usr, npr_lev) +       &
    2038                               ( zu(lpr_lev) - cs_heights(lsp_usr, npr_lev) ) /                          &
    2039                               ( cs_heights(lsp_usr, (npr_lev + 1)) - cs_heights(lsp_usr, npr_lev ) ) *  &
    2040                               ( cs_profile(lsp_usr, (npr_lev + 1)) - cs_profile(lsp_usr, npr_lev ) )
    2041                       ELSE
    2042                          chem_species(lsp)%conc_pr_init(lpr_lev) = cs_profile(lsp_usr, npr_lev)
    2043                       ENDIF
    2044                    ENDDO
    2045                 ENDIF
    2046 !
    2047 !--          If a profile is prescribed explicity using cs_profiles and cs_heights, then 
    2048 !--          chem_species(lsp)%conc_pr_init is populated with the specific "lsp" based
    2049 !--          on the cs_profiles(lsp_usr,:)  and cs_heights(lsp_usr,:).
     2037                   IF ( npr_lev < 100  .AND.  cs_heights(lsp_usr,npr_lev+1) /= 9999999.9_wp )  THEN
     2038                      chem_species(lsp)%conc_pr_init(lpr_lev) = cs_profile(lsp_usr, npr_lev) +       &
     2039                           ( zu(lpr_lev) - cs_heights(lsp_usr, npr_lev) ) /                          &
     2040                           ( cs_heights(lsp_usr, (npr_lev + 1)) - cs_heights(lsp_usr, npr_lev ) ) *  &
     2041                           ( cs_profile(lsp_usr, (npr_lev + 1)) - cs_profile(lsp_usr, npr_lev ) )
     2042                   ELSE
     2043                      chem_species(lsp)%conc_pr_init(lpr_lev) = cs_profile(lsp_usr, npr_lev)
     2044                   ENDIF
     2045                ENDDO
    20502046             ENDIF
    2051           ENDDO
    2052           lsp_usr = lsp_usr + 1
     2047!
     2048!--       If a profile is prescribed explicity using cs_profiles and cs_heights, then 
     2049!--       chem_species(lsp)%conc_pr_init is populated with the specific "lsp" based
     2050!--       on the cs_profiles(lsp_usr,:)  and cs_heights(lsp_usr,:).
     2051          ENDIF
     2052
    20532053       ENDDO
    2054     ENDIF
     2054
     2055       lsp_usr = lsp_usr + 1
     2056    ENDDO
     2057!     ENDIF
    20552058
    20562059 END SUBROUTINE chem_init_profiles
Note: See TracChangeset for help on using the changeset viewer.