Ignore:
Timestamp:
Apr 8, 2014 3:21:23 PM (11 years ago)
Author:
heinze
Message:

REAL constants provided with KIND-attribute

File:
1 edited

Legend:

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

    r1323 r1353  
    2323! Current revisions:
    2424! ------------------
    25 !
     25! REAL constants provided with KIND-attribute
    2626!
    2727! Former revisions:
     
    603603          ALLOCATE( netcdf_data(mask_size(mid,1)) )
    604604
    605           netcdf_data = ( mask_i_global(mid,:mask_size(mid,1)) + 0.5 ) * dx
     605          netcdf_data = ( mask_i_global(mid,:mask_size(mid,1)) + 0.5_wp ) * dx
    606606
    607607          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_x_mask(mid,av), &
     
    623623          ALLOCATE( netcdf_data(mask_size(mid,2)) )
    624624
    625           netcdf_data = ( mask_j_global(mid,:mask_size(mid,2)) + 0.5 ) * dy
     625          netcdf_data = ( mask_j_global(mid,:mask_size(mid,2)) + 0.5_wp ) * dy
    626626
    627627          nc_stat = NF90_PUT_VAR( id_set_mask(mid,av), id_var_y_mask(mid,av), &
     
    11871187
    11881188             DO  i = 0, ny+1
    1189                 netcdf_data(i) = ( i + 0.5 ) * dy
     1189                netcdf_data(i) = ( i + 0.5_wp ) * dy
    11901190             ENDDO
    11911191
     
    17851785             DO  i = 1, ns
    17861786                IF( section(i,1) == -1 )  THEN
    1787                    netcdf_data(i) = -1.0  ! section averaged along z
     1787                   netcdf_data(i) = -1.0_wp  ! section averaged along z
    17881788                ELSE
    17891789                   netcdf_data(i) = zu( section(i,1) )
     
    17991799             DO  i = 1, ns
    18001800                IF( section(i,1) == -1 )  THEN
    1801                    netcdf_data(i) = -1.0  ! section averaged along z
     1801                   netcdf_data(i) = -1.0_wp  ! section averaged along z
    18021802                ELSE
    18031803                   netcdf_data(i) = zw( section(i,1) )
     
    18311831
    18321832             DO  i = 0, nx+1
    1833                 netcdf_data(i) = ( i + 0.5 ) * dx
     1833                netcdf_data(i) = ( i + 0.5_wp ) * dx
    18341834             ENDDO
    18351835
     
    18551855
    18561856             DO  i = 0, ny+1
    1857                 netcdf_data(i) = ( i + 0.5 ) * dy
     1857                netcdf_data(i) = ( i + 0.5_wp ) * dy
    18581858             ENDDO
    18591859
     
    19861986                ENDIF
    19871987             ELSE
    1988                 IF ( -1.0 /= netcdf_data(i) )  THEN
     1988                IF ( -1.0_wp /= netcdf_data(i) )  THEN
    19891989                   message_string = 'netCDF file for cross-sections ' //     &
    19901990                               TRIM( var ) // ' from previous run found,' // &
     
    24372437             DO  i = 1, ns
    24382438                IF( section(i,2) == -1 )  THEN
    2439                    netcdf_data(i) = -1.0  ! section averaged along y
     2439                   netcdf_data(i) = -1.0_wp  ! section averaged along y
    24402440                ELSE
    2441                    netcdf_data(i) = ( section(i,2) + 0.5 ) * dy
     2441                   netcdf_data(i) = ( section(i,2) + 0.5_wp ) * dy
    24422442                ENDIF
    24432443             ENDDO
     
    24512451             DO  i = 1, ns
    24522452                IF( section(i,2) == -1 )  THEN
    2453                    netcdf_data(i) = -1.0  ! section averaged along y
     2453                   netcdf_data(i) = -1.0_wp  ! section averaged along y
    24542454                ELSE
    24552455                   netcdf_data(i) = section(i,2) * dy
     
    24772477
    24782478             DO  i = 0, nx+1
    2479                 netcdf_data(i) = ( i + 0.5 ) * dx
     2479                netcdf_data(i) = ( i + 0.5_wp ) * dx
    24802480             ENDDO
    24812481
     
    26102610                ENDIF
    26112611             ELSE
    2612                 IF ( -1.0 /= netcdf_data(i) )  THEN
     2612                IF ( -1.0_wp /= netcdf_data(i) )  THEN
    26132613                   message_string = 'netCDF file for cross-sections ' //     &
    26142614                               TRIM( var ) // ' from previous run found,' // &
     
    30763076             DO  i = 1, ns
    30773077                IF( section(i,3) == -1 )  THEN
    3078                    netcdf_data(i) = -1.0  ! section averaged along x
     3078                   netcdf_data(i) = -1.0_wp  ! section averaged along x
    30793079                ELSE
    3080                    netcdf_data(i) = ( section(i,3) + 0.5 ) * dx
     3080                   netcdf_data(i) = ( section(i,3) + 0.5_wp ) * dx
    30813081                ENDIF
    30823082             ENDDO
     
    30903090             DO  i = 1, ns
    30913091                IF( section(i,3) == -1 )  THEN
    3092                    netcdf_data(i) = -1.0  ! section averaged along x
     3092                   netcdf_data(i) = -1.0_wp  ! section averaged along x
    30933093                ELSE
    30943094                   netcdf_data(i) = section(i,3) * dx
     
    31153115
    31163116             DO  j = 0, ny+1
    3117                 netcdf_data(j) = ( j + 0.5 ) * dy
     3117                netcdf_data(j) = ( j + 0.5_wp ) * dy
    31183118             ENDDO
    31193119
     
    32483248                ENDIF
    32493249             ELSE
    3250                 IF ( -1.0 /= netcdf_data(i) )  THEN
     3250                IF ( -1.0_wp /= netcdf_data(i) )  THEN
    32513251                   message_string = 'netCDF file for cross-sections ' //    &
    32523252                              TRIM( var ) // ' from previous run found,' // &
     
    33953395!
    33963396!--       Define some global attributes of the dataset
    3397           IF ( averaging_interval_pr /= 0.0 )  THEN
     3397          IF ( averaging_interval_pr /= 0.0_wp )  THEN
    33983398             WRITE (time_average_text,'('', '',F7.1,'' s average'')') &
    33993399                                                            averaging_interval_pr
     
    38203820!--       performance loss due to data copying; an alternative strategy would be
    38213821!--       to ensure equal attribute size in a job chain. Maybe revise later.
    3822           IF ( averaging_interval_pr == 0.0 )  THEN
     3822          IF ( averaging_interval_pr == 0.0_wp )  THEN
    38233823             time_average_text = ' '
    38243824          ELSE
     
    40504050!
    40514051!--       Define some global attributes of the dataset
    4052           IF ( averaging_interval_sp /= 0.0 )  THEN
     4052          IF ( averaging_interval_sp /= 0.0_wp )  THEN
    40534053             WRITE (time_average_text,'('', '',F7.1,'' s average'')') &
    40544054                                                            averaging_interval_sp
     
    42684268          ALLOCATE( netcdf_data(nx/2) )
    42694269          DO  i = 1, nx/2
    4270              netcdf_data(i) = 2.0 * pi * i / ( dx * ( nx + 1 ) )
     4270             netcdf_data(i) = 2.0_wp * pi * i / ( dx * ( nx + 1 ) )
    42714271          ENDDO
    42724272
     
    42794279          ALLOCATE( netcdf_data(ny/2) )
    42804280          DO  i = 1, ny/2
    4281              netcdf_data(i) = 2.0 * pi * i / ( dy * ( ny + 1 ) )
     4281             netcdf_data(i) = 2.0_wp * pi * i / ( dy * ( ny + 1 ) )
    42824282          ENDDO
    42834283
     
    44564456          nc_stat = NF90_REDEF( id_set_sp )
    44574457          CALL handle_netcdf_error( 'netcdf', 441 )
    4458           IF ( averaging_interval_sp /= 0.0 )  THEN
     4458          IF ( averaging_interval_sp /= 0.0_wp )  THEN
    44594459             WRITE (time_average_text,'('', '',F7.1,'' s average'')') &
    44604460                                                           averaging_interval_sp
Note: See TracChangeset for help on using the changeset viewer.