Ignore:
Timestamp:
Jan 22, 2019 10:42:06 AM (5 years ago)
Author:
knoop
Message:

Moved all user routunes that are dependencies of the PALM core only, to user_module.f90
The files that formerly contained these routines, have been deleted.
Also module_interface routines for init_mask and last_actions have been added.

File:
1 edited

Legend:

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

    r3665 r3687  
    164164    USE bulk_cloud_model_mod,                                                  &
    165165        ONLY: bulk_cloud_model, microphysics_morrison, microphysics_seifert
    166 
    167     USE chemistry_model_mod,                                                   &
    168         ONLY:  chem_check_data_output
    169166
    170167    USE control_parameters,                                                    &
     
    190187    USE kinds
    191188
     189    USE module_interface,                                                      &
     190        ONLY:  module_interface_init_masks
     191
    192192    USE netcdf_interface,                                                      &
    193193        ONLY:  domask_unit, netcdf_data_format
     
    196196        ONLY:  particle_advection
    197197
    198     USE pegrid 
    199    
    200     USE radiation_model_mod,                                                   &
    201         ONLY:  radiation_check_data_output
    202        
    203     USE salsa_mod,                                                             &
    204         ONLY:  salsa_check_data_output
     198    USE pegrid
    205199
    206200    IMPLICIT NONE
     
    494488
    495489             CASE DEFAULT
    496              
    497                 CALL user_check_data_output( var, unit )
    498                            
    499                 IF ( salsa )  THEN
    500                    CALL salsa_check_data_output( var, unit )
    501                 ENDIF               
    502 
    503                 IF ( unit == 'illegal'  .AND.  air_chemistry                   &
    504                      .AND.  (var(1:3) == 'kc_' .OR. var(1:3) == 'em_') )  THEN
    505                    CALL chem_check_data_output( var, unit, 0, 0, 0 )
    506                 ENDIF
    507 
    508                 IF ( unit == 'illegal' )  THEN
    509                    CALL radiation_check_data_output( var, unit, 0, 0, 0 )
    510                 ENDIF
     490!
     491!--             Allocate arrays for other modules
     492                CALL module_interface_init_masks( var, unit )
    511493
    512494                IF ( unit == 'illegal' )  THEN
Note: See TracChangeset for help on using the changeset viewer.