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

REAL constants provided with KIND-attribute

File:
1 edited

Legend:

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

    r1329 r1353  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! REAL constants provided with KIND-attribute
    2323!
    2424! Former revisions:
     
    235235             ns = ns - 1
    236236             ALLOCATE( local_2d_sections(nxlg:nxrg,nysg:nyng,1:ns) )
    237              local_2d_sections = 0.0
     237             local_2d_sections = 0.0_wp
    238238          ENDIF
    239239
     
    266266             ALLOCATE( local_2d_sections(nxlg:nxrg,1:ns,nzb:nzt+1) )
    267267             ALLOCATE( local_2d_sections_l(nxlg:nxrg,1:ns,nzb:nzt+1) )
    268              local_2d_sections = 0.0; local_2d_sections_l = 0.0
     268             local_2d_sections = 0.0_wp; local_2d_sections_l = 0.0_wp
    269269          ENDIF
    270270
     
    297297             ALLOCATE( local_2d_sections(1:ns,nysg:nyng,nzb:nzt+1) )
    298298             ALLOCATE( local_2d_sections_l(1:ns,nysg:nyng,nzb:nzt+1) )
    299              local_2d_sections = 0.0; local_2d_sections_l = 0.0
     299             local_2d_sections = 0.0_wp; local_2d_sections_l = 0.0_wp
    300300          ENDIF
    301301
     
    400400                      CALL exchange_horiz( tend, nbgp )
    401401                   ELSE
    402                       tend = 0.0
     402                      tend = 0.0_wp
    403403                   ENDIF
    404404                   DO  i = nxlg, nxrg
     
    422422                            DO  k = nzb, nzt+1
    423423                               psi = prt_start_index(k,j,i)
    424                                s_r3 = 0.0
    425                                s_r4 = 0.0
     424                               s_r3 = 0.0_wp
     425                               s_r4 = 0.0_wp
    426426                               DO  n = psi, psi+prt_count(k,j,i)-1
    427427                                  s_r3 = s_r3 + particles(n)%radius**3 *       &
     
    430430                                                particles(n)%weight_factor
    431431                               ENDDO
    432                                IF ( s_r3 /= 0.0 )  THEN
     432                               IF ( s_r3 /= 0.0_wp )  THEN
    433433                                  mean_r = s_r4 / s_r3
    434434                               ELSE
    435                                   mean_r = 0.0
     435                                  mean_r = 0.0_wp
    436436                               ENDIF
    437437                               tend(k,j,i) = mean_r
     
    441441                      CALL exchange_horiz( tend, nbgp )
    442442                   ELSE
    443                       tend = 0.0
     443                      tend = 0.0_wp
    444444                   END IF
    445445                   DO  i = nxlg, nxrg
     
    463463                   ENDDO
    464464                ENDDO
    465                 precipitation_amount = 0.0   ! reset for next integ. interval
     465                precipitation_amount = 0.0_wp   ! reset for next integ. interval
    466466                resorted = .TRUE.
    467467                two_d = .TRUE.
     
    608608                      CALL exchange_horiz( tend, nbgp )
    609609                   ELSE
    610                       tend = 0.0
     610                      tend = 0.0_wp
    611611                   END IF
    612612                   DO  i = nxlg, nxrg
     
    733733!--             at the bottom boundary by the real surface values.
    734734                IF ( do2d(av,if) == 'u_xz'  .OR.  do2d(av,if) == 'u_yz' )  THEN
    735                    IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0
     735                   IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0_wp
    736736                ENDIF
    737737
     
    765765!--             at the bottom boundary by the real surface values.
    766766                IF ( do2d(av,if) == 'v_xz'  .OR.  do2d(av,if) == 'v_yz' )  THEN
    767                    IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0
     767                   IF ( ibc_uv_b == 0 )  local_pf(:,:,nzb) = 0.0_wp
    768768                ENDIF
    769769
     
    898898                   IF ( section(is,s) == -1  .AND.  .NOT. two_d )  THEN
    899899
    900                       local_2d = 0.0
     900                      local_2d = 0.0_wp
    901901!
    902902!--                   Carry out the averaging (all data are on the PE)
     
    909909                      ENDDO
    910910
    911                       local_2d = local_2d / ( nzt -nzb + 2.0)
     911                      local_2d = local_2d / ( nzt -nzb + 2.0_wp)
    912912
    913913                   ELSE
     
    10891089
    10901090                      ALLOCATE( local_2d_l(nxlg:nxrg,nzb:nzt+1) )
    1091                       local_2d_l = 0.0
     1091                      local_2d_l = 0.0_wp
    10921092                      ngp = ( nxrg-nxlg+1 ) * ( nzt-nzb+2 )
    10931093!
     
    11111111                      local_2d = local_2d_l
    11121112#endif
    1113                       local_2d = local_2d / ( ny + 1.0 )
     1113                      local_2d = local_2d / ( ny + 1.0_wp )
    11141114
    11151115                      DEALLOCATE( local_2d_l )
     
    13081308
    13091309                      ALLOCATE( local_2d_l(nysg:nyng,nzb:nzt+1) )
    1310                       local_2d_l = 0.0
     1310                      local_2d_l = 0.0_wp
    13111311                      ngp = ( nyng-nysg+1 ) * ( nzt-nzb+2 )
    13121312!
     
    13301330                      local_2d = local_2d_l
    13311331#endif
    1332                       local_2d = local_2d / ( nx + 1.0 )
     1332                      local_2d = local_2d / ( nx + 1.0_wp )
    13331333
    13341334                      DEALLOCATE( local_2d_l )
Note: See TracChangeset for help on using the changeset viewer.