Ignore:
Timestamp:
Jan 21, 2019 1:02:11 AM (5 years ago)
Author:
knoop
Message:

Some interface calls moved to module_interface + cleanup

File:
1 edited

Legend:

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

    r3611 r3685  
    2222! Current revisions:
    2323! ------------------
    24 !
     24! 
    2525!
    2626! Former revisions:
    2727! -----------------
    2828! $Id$
     29! Some interface calls moved to module_interface + cleanup
     30!
     31! 3611 2018-12-07 14:14:11Z banzhafs
    2932! Code update to comply PALM coding rules
    3033! removed unnecessary informative messsages/location
     
    693696!> fluxes at timestep 0
    694697!------------------------------------------------------------------------------!
    695  SUBROUTINE chem_emissions_init( emt_att, emt, nspec_out )
     698 SUBROUTINE chem_emissions_init
    696699
    697700    USE surface_mod,                                                           &
    698701        ONLY:  surf_def_h, surf_lsm_h, surf_usm_h
     702
     703    USE netcdf_data_input_mod,                                                 &
     704        ONLY:  chem_emis, chem_emis_att
    699705   
    700706    IMPLICIT NONE
    701707 
    702708    CHARACTER (LEN=80)          ::  units                                           !< units of inputs
    703    
    704     INTEGER(iwp), INTENT(INOUT) ::  nspec_out                                       !< number of outputs
    705709
    706710    INTEGER(iwp)                :: ispec                                            !< running index
    707 
    708     TYPE(chem_emis_att_type), INTENT(INOUT) ::  emt_att                             !< variable where to store all the information
    709                                                                                     !< of emission inputs whose values do not
    710                                                                                     !< depend on the considered species
    711 
    712     TYPE(chem_emis_val_type), INTENT(INOUT), ALLOCATABLE, DIMENSION(:) ::  emt      !< variable where to store emission input 
    713                                                                                     !< values depending on the considered species
    714711
    715712!   
     
    730727  !
    731728  !-- Matching
    732   CALL  chem_emissions_match( emt_att, nspec_out )
     729  CALL  chem_emissions_match( chem_emis_att, nspec_out )
    733730 
    734731  IF ( nspec_out == 0 )  THEN
     
    743740     !
    744741     !-- Set molecule masses'
    745      ALLOCATE( emt_att%xm(nspec_out) )
     742     ALLOCATE( chem_emis_att%xm(nspec_out) )
    746743
    747744     DO ispec = 1, nspec_out
    748745        SELECT CASE ( TRIM( spc_names(match_spec_model(ispec)) ) )
    749            CASE ( 'SO2' ); emt_att%xm(ispec) = xm_S + xm_O * 2        !< kg/mole
    750            CASE ( 'SO4' ); emt_att%xm(ispec) = xm_S + xm_O * 4        !< kg/mole
    751            CASE ( 'NO' ); emt_att%xm(ispec) = xm_N + xm_O             !< kg/mole
    752            CASE ( 'NO2' ); emt_att%xm(ispec) = xm_N + xm_O * 2        !< kg/mole   
    753            CASE ( 'NH3' ); emt_att%xm(ispec) = xm_N + xm_H * 3        !< kg/mole
    754            CASE ( 'CO'  ); emt_att%xm(ispec) = xm_C + xm_O            !< kg/mole
    755            CASE ( 'CO2' ); emt_att%xm(ispec) = xm_C + xm_O * 2        !< kg/mole
    756            CASE ( 'CH4' ); emt_att%xm(ispec) = xm_C + xm_H * 4        !< kg/mole     
    757            CASE ( 'HNO3' ); emt_att%xm(ispec) = xm_H + xm_N + xm_O*3  !< kg/mole 
     746           CASE ( 'SO2' ); chem_emis_att%xm(ispec) = xm_S + xm_O * 2        !< kg/mole
     747           CASE ( 'SO4' ); chem_emis_att%xm(ispec) = xm_S + xm_O * 4        !< kg/mole
     748           CASE ( 'NO' ); chem_emis_att%xm(ispec) = xm_N + xm_O             !< kg/mole
     749           CASE ( 'NO2' ); chem_emis_att%xm(ispec) = xm_N + xm_O * 2        !< kg/mole   
     750           CASE ( 'NH3' ); chem_emis_att%xm(ispec) = xm_N + xm_H * 3        !< kg/mole
     751           CASE ( 'CO'  ); chem_emis_att%xm(ispec) = xm_C + xm_O            !< kg/mole
     752           CASE ( 'CO2' ); chem_emis_att%xm(ispec) = xm_C + xm_O * 2        !< kg/mole
     753           CASE ( 'CH4' ); chem_emis_att%xm(ispec) = xm_C + xm_H * 4        !< kg/mole     
     754           CASE ( 'HNO3' ); chem_emis_att%xm(ispec) = xm_H + xm_N + xm_O*3  !< kg/mole 
    758755           CASE DEFAULT
    759               emt_att%xm(ispec) = 1.0_wp
     756              chem_emis_att%xm(ispec) = 1.0_wp
    760757        END SELECT
    761758     ENDDO
     
    775772           !
    776773           !-- Get emissions at the first time step
    777            CALL chem_emissions_setup( emt_att, emt, nspec_out )
     774           CALL chem_emissions_setup( chem_emis_att, chem_emis, nspec_out )
    778775
    779776        !
     
    785782           !
    786783           !-- Get emissions at the first time step
    787            CALL chem_emissions_setup( emt_att, emt, nspec_out )
     784           CALL chem_emissions_setup( chem_emis_att, chem_emis, nspec_out )
    788785
    789786        !
     
    795792           !
    796793           !-- Get emissions at the first time step
    797            CALL chem_emissions_setup( emt_att, emt, nspec_out)
     794           CALL chem_emissions_setup( chem_emis_att, chem_emis, nspec_out)
    798795
    799796     END SELECT
Note: See TracChangeset for help on using the changeset viewer.