Changeset 4268 for palm/trunk/SOURCE/chemistry_model_mod.f90
- Timestamp:
- Oct 17, 2019 11:29:38 AM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chemistry_model_mod.f90
r4230 r4268 27 27 ! ----------------- 28 28 ! $Id$ 29 ! Moving module specific boundary conditions from time_integration to module 30 ! 31 ! 4230 2019-09-11 13:58:14Z suehring 29 32 ! Bugfix, initialize mean profiles also in restart runs. Also initialize 30 33 ! array used for Runge-Kutta tendecies in restart runs. … … 380 383 END INTERFACE chem_boundary_conds 381 384 385 INTERFACE chem_boundary_conditions 386 MODULE PROCEDURE chem_boundary_conditions 387 END INTERFACE chem_boundary_conditions 388 382 389 INTERFACE chem_check_data_output 383 390 MODULE PROCEDURE chem_check_data_output … … 537 544 538 545 539 PUBLIC chem_3d_data_averaging, chem_boundary_conds, 546 PUBLIC chem_3d_data_averaging, chem_boundary_conds, chem_boundary_conditions, & 540 547 chem_boundary_conds_decycle, chem_check_data_output, & 541 548 chem_check_data_output_pr, chem_check_parameters, & … … 799 806 END SUBROUTINE chem_boundary_conds 800 807 808 !------------------------------------------------------------------------------! 809 ! Description: 810 ! ------------ 811 !> Subroutine for boundary conditions 812 !------------------------------------------------------------------------------! 813 SUBROUTINE chem_boundary_conditions 814 815 IMPLICIT NONE 816 817 INTEGER(iwp) :: lsp !< 818 INTEGER(iwp) :: lsp_usr !< 819 820 ! 821 !-- Boundary conditions for prognostic quantitites of other modules: 822 !-- Here, only decycling is carried out 823 824 DO lsp = 1, nvar 825 lsp_usr = 1 826 DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' ) 827 IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) ) THEN 828 CALL chem_boundary_conds( chem_species(lsp)%conc_p, & 829 chem_species(lsp)%conc_pr_init ) 830 ENDIF 831 lsp_usr = lsp_usr + 1 832 ENDDO 833 ENDDO 834 835 836 END SUBROUTINE chem_boundary_conditions 801 837 802 838 !------------------------------------------------------------------------------!
Note: See TracChangeset
for help on using the changeset viewer.