Ignore:
Timestamp:
Dec 11, 2020 2:18:43 PM (3 years ago)
Author:
raasch
Message:

reading of namelist file and actions in case of namelist errors revised so that statement labels and goto statements are not required any more

File:
1 edited

Legend:

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

    r4768 r4822  
    2626! -----------------
    2727! $Id$
     28! reading of namelist file and actions in case of namelist errors revised so that statement labels
     29! and goto statements are not required any more
     30!
     31! 4768 2020-11-02 19:11:23Z suehring
    2832! Enable 3D data output also with 64-bit precision
    2933!
     
    4347! - Bugfix in variable name separation in profile-output initialization
    4448! - Bugfix in counting the number of chemistry profiles
    45 ! 
     49!
    4650! 4581 2020-06-29 08:49:58Z suehring
    4751! Enable output of resolved-scale vertical fluxes of chemical species.
    48 ! 
     52!
    4953! 4577 2020-06-25 09:53:58Z raasch
    5054! further re-formatting to follow the PALM coding standard
     
    25042508
    25052509
    2506     CHARACTER (LEN=80) ::  line                        !< dummy string that contains the current
     2510    CHARACTER(LEN=100) ::  line                        !< dummy string that contains the current
    25072511                                                       !< line of the parameter file
     2512    CHARACTER(LEN=8)   ::  solver_type
    25082513
    25092514    INTEGER(iwp) ::  i                                 !<
     2515    INTEGER(iwp) ::  io_status                         !< Status after reading the namelist file
    25102516    INTEGER(iwp) ::  max_pr_cs_tmp                     !<
    25112517
     
    25662572    !>  If the respective concentration profile should be constant with height, then use "cs_surface( number of spcs)"
    25672573    !>  then write these cs_surface values to chem_species(lsp)%conc_pr_init(:)
     2574
    25682575!
    25692576!-- Read chem namelist
    2570     CHARACTER(LEN=8)    :: solver_type
    2571 
    25722577    icntrl    = 0
    25732578    rcntrl    = 0.0_wp
     
    25772582    rtol = 0.01_wp
    25782583!
    2579 !-- Try to find chemistry package
    2580     REWIND ( 11 )
    2581     line = ' '
    2582     DO   WHILE ( INDEX( line, '&chemistry_parameters' ) == 0 )
    2583        READ ( 11, '(A)', END=20 )  line
    2584     ENDDO
    2585     BACKSPACE ( 11 )
    2586 !
    2587 !-- Read chemistry namelist
    2588     READ ( 11, chemistry_parameters, ERR = 10, END = 20 )
    2589 !
    2590 !-- Enable chemistry model
    2591     air_chemistry = .TRUE.
    2592     GOTO 20
    2593 
    2594  10 BACKSPACE( 11 )
    2595     READ( 11 , '(A)') line
    2596     CALL parin_fail_message( 'chemistry_parameters', line )
    2597 
    2598  20 CONTINUE
    2599 
    2600 
     2584!-- Move to the beginning of the namelist file and try to find and read the namelist named
     2585!-- chemistry_parameters.
     2586    REWIND( 11 )
     2587    READ( 11, chemistry_parameters, IOSTAT=io_status )
     2588!
     2589!-- Action depending on the READ status
     2590    IF ( io_status == 0 )  THEN
     2591!
     2592!      chemistry_parameters namelist was found and read correctly. Switch on chemistry model.
     2593       air_chemistry = .TRUE.
     2594
     2595    ELSEIF ( io_status > 0 )  THEN
     2596!
     2597!--    chemistry_parameters namelist was found, but contained errors. Print an error message
     2598!--    including the line that caused the problem.
     2599       BACKSPACE( 11 )
     2600       READ( 11 , '(A)') line
     2601       CALL parin_fail_message( 'chemistry_parameters', line )
     2602
     2603    ENDIF
    26012604
    26022605!
     
    27432746!
    27442747!-- Set Solver Type
    2745     IF(icntrl(3) == 0)  THEN
     2748    IF ( icntrl(3) == 0 )  THEN
    27462749       solver_type = 'rodas3'           !Default
    2747     ELSE IF(icntrl(3) == 1)  THEN
     2750    ELSEIF ( icntrl(3) == 1 )  THEN
    27482751       solver_type = 'ros2'
    2749     ELSE IF(icntrl(3) == 2)  THEN
     2752    ELSEIF ( icntrl(3) == 2 )  THEN
    27502753       solver_type = 'ros3'
    2751     ELSE IF(icntrl(3) == 3)  THEN
     2754    ELSEIF ( icntrl(3) == 3 )  THEN
    27522755       solver_type = 'ro4'
    2753     ELSE IF(icntrl(3) == 4)  THEN
     2756    ELSEIF ( icntrl(3) == 4 )  THEN
    27542757       solver_type = 'rodas3'
    2755     ELSE IF(icntrl(3) == 5)  THEN
     2758    ELSEIF ( icntrl(3) == 5 )  THEN
    27562759       solver_type = 'rodas4'
    2757     ELSE IF(icntrl(3) == 6)  THEN
     2760    ELSEIF ( icntrl(3) == 6 )  THEN
    27582761       solver_type = 'Rang3'
    27592762    ELSE
     
    33513354!--    Sum-up profiles for vertical fluxes of the the species. Note, in case of WS5 scheme the
    33523355!--    profiles of resolved-scale fluxes have been already summed-up, while resolved-scale fluxes
    3353 !--    need to be calculated in case of PW scheme. 
     3356!--    need to be calculated in case of PW scheme.
    33543357!--    For summation employ a temporary array.
    33553358       !$OMP PARALLEL PRIVATE( i, j, k, tn, lpr, sums_tmp, flag )
Note: See TracChangeset for help on using the changeset viewer.