Changeset 2874 for palm


Ignore:
Timestamp:
Mar 13, 2018 10:55:42 AM (6 years ago)
Author:
knoop
Message:

Bugfix: wrong placement of netcdf cpp-macros fixed

File:
1 edited

Legend:

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

    r2794 r2874  
    2525! -----------------
    2626! $Id$
     27! Bugfix: wrong placement of netcdf cpp-macros fixed
     28!
     29! 2794 2018-02-07 14:09:43Z knoop
    2730! Check if 3D building input is consistent to numeric grid.
    2831!
     
    16351638       DO  ii = 0, io_blocks-1
    16361639          IF ( ii == io_group )  THEN
    1637 #if defined ( __netcdf )
    16381640!
    16391641!--          Input via palm-input data standard
    16401642             IF ( input_pids_static )  THEN
     1643#if defined ( __netcdf )
    16411644!
    16421645!--             Open file in read-only mode
     
    17741777!--             Close topography input file
    17751778                CALL close_input_file( id_topo )
     1779#else
     1780                CONTINUE
    17761781#endif
    17771782!
     
    34553460     SUBROUTINE get_attribute_int32( id, attribute_name, value, global,        &
    34563461                                     variable_name )
    3457 #if defined( __netcdf )
    34583462
    34593463       USE pegrid
     
    34693473
    34703474       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
     3475#if defined( __netcdf )
    34713476
    34723477!
     
    34943499     SUBROUTINE get_attribute_int8( id, attribute_name, value, global,         &
    34953500                                    variable_name )
    3496 #if defined( __netcdf )
    34973501
    34983502       USE pegrid
     
    35083512
    35093513       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
     3514#if defined( __netcdf )
    35103515
    35113516!
     
    35333538     SUBROUTINE get_attribute_real( id, attribute_name, value, global,         &
    35343539                                    variable_name )
    3535 #if defined( __netcdf )
    35363540
    35373541       USE pegrid
     
    35483552
    35493553       REAL(wp), INTENT(INOUT)     ::  value            !< read value
     3554#if defined( __netcdf )
    35503555
    35513556
     
    35763581     SUBROUTINE get_attribute_string( id, attribute_name, value, global,       &
    35773582                                      variable_name )
    3578 #if defined( __netcdf )
    35793583
    35803584       USE pegrid
     
    35903594
    35913595       LOGICAL, INTENT(IN) ::  global                   !< flag indicating global attribute
     3596#if defined( __netcdf )
    35923597
    35933598!
     
    36493654!------------------------------------------------------------------------------!
    36503655     SUBROUTINE get_variable_1d_int( id, variable_name, var )
    3651 #if defined( __netcdf )
    36523656
    36533657       USE pegrid
     
    36613665
    36623666       INTEGER(iwp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
     3667#if defined( __netcdf )
    36633668
    36643669!
     
    36803685!------------------------------------------------------------------------------!
    36813686     SUBROUTINE get_variable_1d_real( id, variable_name, var )
    3682 #if defined( __netcdf )
    36833687
    36843688       USE pegrid
     
    36923696
    36933697       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var  !< variable to be read
     3698#if defined( __netcdf )
    36943699
    36953700!
     
    37123717!------------------------------------------------------------------------------!
    37133718    SUBROUTINE get_variable_2d_real( id, variable_name, i, var )
    3714 #if defined( __netcdf )
    37153719
    37163720       USE indices
     
    37263730
    37273731       REAL(wp), DIMENSION(nys:nyn), INTENT(INOUT) ::  var  !< variable to be read
     3732#if defined( __netcdf )
    37283733!
    37293734!--    Inquire variable id
     
    37463751!------------------------------------------------------------------------------!
    37473752    SUBROUTINE get_variable_2d_int32( id, variable_name, i, var )
    3748 #if defined( __netcdf )
    37493753
    37503754       USE indices
     
    37593763       INTEGER(iwp)                  ::  id_var          !< variable id
    37603764       INTEGER(iwp), DIMENSION(nys:nyn), INTENT(INOUT) ::  var  !< variable to be read
     3765#if defined( __netcdf )
    37613766!
    37623767!--    Inquire variable id
     
    37793784!------------------------------------------------------------------------------!
    37803785    SUBROUTINE get_variable_2d_int8( id, variable_name, i, var )
    3781 #if defined( __netcdf )
    37823786
    37833787       USE indices
     
    37923796       INTEGER(iwp)                  ::  id_var          !< variable id
    37933797       INTEGER(KIND=1), DIMENSION(nys:nyn), INTENT(INOUT) ::  var  !< variable to be read
     3798#if defined( __netcdf )
    37943799!
    37953800!--    Inquire variable id
     
    38113816!------------------------------------------------------------------------------!
    38123817    SUBROUTINE get_variable_3d_int8( id, variable_name, i, j, var )
    3813 #if defined( __netcdf )
    38143818
    38153819       USE indices
     
    38293833
    38303834       INTEGER( KIND = 1 ), DIMENSION(nzb:nzt+1), INTENT(INOUT) ::  var  !< variable to be read
     3835#if defined( __netcdf )
    38313836
    38323837!
     
    38553860!------------------------------------------------------------------------------!
    38563861    SUBROUTINE get_variable_3d_real( id, variable_name, i, j, var )
    3857 #if defined( __netcdf )
    38583862
    38593863       USE indices
     
    38733877
    38743878       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var     !< variable to be read
     3879#if defined( __netcdf )
    38753880
    38763881!
     
    39003905!------------------------------------------------------------------------------!
    39013906    SUBROUTINE get_variable_4d_real( id, variable_name, i, j, var, n3, n4 )
    3902 #if defined( __netcdf )
    39033907
    39043908       USE indices
     
    39193923
    39203924       REAL(wp), DIMENSION(:,:), INTENT(INOUT) ::  var     !< variable to be read
     3925#if defined( __netcdf )
    39213926
    39223927!
     
    39423947    SUBROUTINE get_variable_bc( id, variable_name, t_start,                    &
    39433948                                i2_s, count_2, i3_s, count_3,  var )
    3944 #if defined( __netcdf )
    39453949
    39463950       USE indices
     
    39603964
    39613965       REAL(wp), DIMENSION(:), INTENT(INOUT) ::  var     !< input variable
     3966#if defined( __netcdf )
    39623967
    39633968!
     
    39823987!------------------------------------------------------------------------------!
    39833988    SUBROUTINE inquire_num_variables( id, num_vars )
    3984 #if defined( __netcdf )
    39853989
    39863990       USE indices
     
    39913995       INTEGER(iwp), INTENT(IN)      ::  id              !< file id
    39923996       INTEGER(iwp), INTENT(INOUT)   ::  num_vars        !< number of variables in a file
     3997#if defined( __netcdf )
    39933998
    39943999       nc_stat = NF90_INQUIRE( id, NVARIABLES = num_vars )
     
    40054010!------------------------------------------------------------------------------!
    40064011    SUBROUTINE inquire_variable_names( id, var_names )
    4007 #if defined( __netcdf )
    40084012
    40094013       USE indices
     
    40174021       INTEGER(iwp)                                  ::  num_vars    !< number of variables (unused return parameter)
    40184022       INTEGER(iwp), DIMENSION(:), ALLOCATABLE       ::  varids      !< dummy array to strore variable ids temporarily
     4023#if defined( __netcdf )
    40194024
    40204025       ALLOCATE( varids(1:SIZE(var_names)) )
     
    40374042!------------------------------------------------------------------------------!
    40384043    SUBROUTINE handle_error( routine_name, errno )
    4039 #if defined( __netcdf )
    40404044
    40414045       USE control_parameters,                                                 &
     
    40484052
    40494053       INTEGER(iwp) ::  errno
     4054#if defined( __netcdf )
    40504055
    40514056       IF ( nc_stat /= NF90_NOERR )  THEN
Note: See TracChangeset for help on using the changeset viewer.