Ignore:
Timestamp:
Oct 17, 2019 11:29:38 AM (5 years ago)
Author:
schwenkel
Message:

Introducing module interface for boundary conditions and move module specific boundary conditions into their modules

File:
1 edited

Legend:

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

    r4227 r4268  
    2525! -----------------
    2626! $Id$
     27! Removing module specific boundary conditions an put them into their modules
     28!
     29! 4227 2019-09-10 18:04:34Z gronemeier
    2730! implement new palm_date_time_mod
    2831!
     
    254257
    255258    USE module_interface,                                                                          &
    256         ONLY:  module_interface_actions, module_interface_swap_timelevel
     259        ONLY:  module_interface_actions, module_interface_swap_timelevel,                          &
     260               module_interface_boundary_conditions
    257261
    258262    USE multi_agent_system_mod,                                                                    &
     
    583587!--    Execute all other module actions routunes
    584588       CALL module_interface_actions( 'before_timestep' )
    585        
     589
    586590!
    587591!--    Start of intermediate step loop
     
    750754!--       velocities at the outflow in case of a non-cyclic lateral wall)
    751755          CALL boundary_conds
    752 
    753 !
    754 !--       Boundary conditions for prognostic quantitites of other modules:
    755 !--       Here, only decycling is carried out
    756           IF ( air_chemistry )  THEN
    757 
    758              DO  lsp = 1, nvar
    759                 lsp_usr = 1
    760                 DO WHILE ( TRIM( cs_name( lsp_usr ) ) /= 'novalue' )
    761                    IF ( TRIM( chem_species(lsp)%name ) == TRIM( cs_name(lsp_usr) ) )  THEN
    762                       CALL chem_boundary_conds( chem_species(lsp)%conc_p,                          &
    763                                                 chem_species(lsp)%conc_pr_init )
    764                    ENDIF
    765                    lsp_usr = lsp_usr + 1
    766                 ENDDO
    767              ENDDO
    768 
    769           ENDIF
    770 
    771           IF ( salsa  .AND.  time_since_reference_point >= skip_time_do_salsa )  THEN
    772 
    773              DO  ib = 1, nbins_aerosol
    774                 CALL salsa_boundary_conds( aerosol_number(ib)%conc_p, aerosol_number(ib)%init )
    775                 DO  ic = 1, ncomponents_mass
    776                    icc = ( ic - 1 ) * nbins_aerosol + ib
    777                    CALL salsa_boundary_conds( aerosol_mass(icc)%conc_p, aerosol_mass(icc)%init )
    778                 ENDDO
    779              ENDDO
    780              IF ( .NOT. salsa_gases_from_chem )  THEN
    781                 DO  ig = 1, ngases_salsa
    782                    CALL salsa_boundary_conds( salsa_gas(ig)%conc_p, salsa_gas(ig)%init )
    783                 ENDDO
    784              ENDIF
    785 
    786           ENDIF
    787 
     756!
     757!--       Boundary conditions for module-specific variables
     758          CALL module_interface_boundary_conditions
    788759!
    789760!--       Incrementing timestep counter
     
    1009980
    1010981             ELSE
    1011 !               
     982!
    1012983!--             Mass (volume) flux correction to ensure global mass conservation for child domains.
    1013984                IF ( child_domain )  THEN
     
    1018989                   ENDIF
    1019990                ENDIF
    1020                
     991
    1021992                CALL pres
    1022993
     
    10841055                CALL lsm_energy_balance( .FALSE., 3 )
    10851056                CALL lsm_soil_model( .FALSE., 3, .TRUE. )
    1086                
     1057
    10871058!
    10881059!--             At the end, set boundary conditons for potential temperature
     
    10911062                CALL lsm_boundary_condition
    10921063
    1093                
     1064
    10941065                CALL cpu_log( log_point(54), 'land_surface', 'stop' )
    10951066             ENDIF
     
    10991070             IF (urban_surface) THEN
    11001071                CALL cpu_log( log_point(74), 'urban_surface', 'start' )
    1101                
     1072
    11021073                CALL usm_surface_energy_balance( .FALSE. )
    11031074                IF ( usm_material_model )  THEN
Note: See TracChangeset for help on using the changeset viewer.