Ignore:
Timestamp:
Oct 18, 2018 3:25:56 PM (6 years ago)
Author:
kanani
Message:

Fix cpp directives and error messages

File:
1 edited

Legend:

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

    r3337 r3373  
    2727! -----------------
    2828! $Id$
     29! Fix wrong location of __netcdf directive
     30!
     31! 3337 2018-10-12 15:17:09Z kanani
    2932! (from branch resler)
    3033! Formatting
     
    6568    USE kinds
    6669
    67 #if defined ( __netcdf )
    68 
    6970    USE netcdf_data_input_mod,                                                  &
    7071       ONLY: chem_emis_att_type, chem_emis_val_type
    7172
     73#if defined ( __netcdf )
    7274    USE NETCDF
    73 
    7475#endif
    7576
     
    779780 SUBROUTINE chem_emissions_init(emt_att,emt,nspec_out)
    780781
    781 #if defined( __netcdf )
     782
    782783
    783784    USE surface_mod,                                                           &
     
    798799 
    799800    INTEGER(iwp)                                                      :: ispec     !> Index to go through the emission chemical species
    800 
     801#if defined( __netcdf )
    801802
    802803!-- Actions for initial runs : TBD: needs to be updated
     
    918919 IMPLICIT NONE
    919920
    920 #if defined( __netcdf )
     921
    921922 
    922923    !--- IN/OUT
     
    983984    REAL(wp), PARAMETER   ::  ratio2ppm  = 1.0e06_wp 
    984985    !------------------------------------------------------   
    985 
     986#if defined( __netcdf )
    986987    IF ( emission_output_required ) THEN
    987988
Note: See TracChangeset for help on using the changeset viewer.