Changeset 3887 for palm/trunk/SOURCE/chemistry_model_mod.f90
- Timestamp:
- Apr 12, 2019 8:47:41 AM (6 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/chemistry_model_mod.f90
r3886 r3887 522 522 MODULE PROCEDURE chem_non_transport_physics_ij 523 523 END INTERFACE chem_non_transport_physics 524 525 INTERFACE chem_exchange_horiz 526 MODULE PROCEDURE chem_exchange_horiz 527 END INTERFACE chem_exchange_horiz 524 528 525 529 INTERFACE chem_prognostic_equations … … 622 626 chem_actions, chem_prognostic_equations, chem_rrd_local, & 623 627 chem_statistics, chem_swap_timelevel, chem_wrd_local, chem_depo, & 624 chem_non_transport_physics 628 chem_non_transport_physics, chem_exchange_horiz 625 629 626 630 CONTAINS … … 915 919 DO lsp = 1, nspec 916 920 917 CALL exchange_horiz( chem_species(lsp)%conc _p, nbgp )921 CALL exchange_horiz( chem_species(lsp)%conc, nbgp ) 918 922 lsp_usr = 1 919 923 DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' ) … … 2460 2464 2461 2465 END SUBROUTINE chem_non_transport_physics_ij 2466 2467 SUBROUTINE chem_exchange_horiz 2468 2469 2470 INTEGER(iwp) :: i !< grid index in x-direction 2471 INTEGER(iwp) :: j !< grid index in y-direction 2472 2473 i = i + j 2474 ! ! 2475 ! !-- Loop over chemical species 2476 ! CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'start' ) 2477 ! DO lsp = 1, nspec 2478 ! CALL exchange_horiz( chem_species(lsp)%conc, nbgp ) 2479 ! lsp_usr = 1 2480 ! DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' ) 2481 ! IF ( TRIM(chem_species(lsp)%name) == TRIM(cs_name(lsp_usr)) ) THEN 2482 ! 2483 ! CALL chem_boundary_conds( chem_species(lsp)%conc_p, & 2484 ! chem_species(lsp)%conc_pr_init ) 2485 ! 2486 ! ENDIF 2487 ! lsp_usr = lsp_usr +1 2488 ! ENDDO 2489 ! 2490 ! 2491 ! ENDDO 2492 ! CALL cpu_log( log_point_s(84), 'chem.exch-horiz', 'stop' ) 2493 2494 2495 END SUBROUTINE chem_exchange_horiz 2496 2462 2497 2463 2498
Note: See TracChangeset
for help on using the changeset viewer.