Ignore:
Timestamp:
Nov 2, 2018 2:19:26 PM (5 years ago)
Author:
raasch
Message:

bugfix: misplaced positions of cpp-directives for netCDF and MPI fixed; output format limited to a maximum line length of 80

File:
1 edited

Legend:

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

    r3467 r3483  
    2727! -----------------
    2828! $Id$
     29! bugfix: wrong locations of netCDF directives fixed
     30!
     31! 3467 2018-10-30 19:05:21Z suehring
    2932! Enabled PARAMETRIZED mode for default surfaces when LSM is not applied but
    3033! salsa is used
     
    8588
    8689#if defined ( __netcdf )
     90    USE NETCDF
     91#endif
    8792
    8893    USE netcdf_data_input_mod,                                                  &
    8994       ONLY: chem_emis_att_type, chem_emis_val_type
    90 
    91     USE NETCDF
    92 
    93 #endif
    9495
    9596    USE date_and_time_mod,                                                      &
     
    192193
    193194    !> Boltzmann constant:
    194     REAL, PARAMETER        ::  kbolz = 1.38066e-23_wp    ! J/K
     195    REAL(wp), PARAMETER     ::  kbolz = 1.38066e-23_wp    ! J/K
    195196
    196197    !> Inverse Reference Pressure (1/Pa)   
     
    758759 SUBROUTINE chem_emissions_init(emt_att,emt,nspec_out)
    759760
    760 #if defined( __netcdf )
    761 
    762761    USE surface_mod,                                                           &
    763762       ONLY:  surf_lsm_h,surf_def_h,surf_usm_h
     
    868867  ENDIF   
    869868
    870 #endif
    871 
    872 
    873869 END SUBROUTINE chem_emissions_init
    874870
     
    899895
    900896 IMPLICIT NONE
    901 
    902 #if defined( __netcdf )
    903897 
    904898    !--- IN/OUT
     
    17161710
    17171711
    1718 #endif
    1719 
    17201712 END SUBROUTINE chem_emissions_setup
    17211713
Note: See TracChangeset for help on using the changeset viewer.