Ignore:
Timestamp:
Mar 20, 2014 4:38:49 PM (10 years ago)
Author:
raasch
Message:

REAL functions and a lot of REAL constants provided with KIND-attribute,
some small bugfixes

File:
1 edited

Legend:

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

    r1321 r1322  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! REAL constants defined as wp-kind
    2323!
    2424! Former revisions:
     
    377377!-- Compute the grid-dependent mixing length.
    378378    DO  k = 1, nzt
    379        l_grid(k)  = ( dx * dy * dzw(k) )**0.33333333333333
     379       l_grid(k)  = ( dx * dy * dzw(k) )**0.33333333333333_wp
    380380    ENDDO
    381381
     
    516516          bh  = NINT( building_height / dz )
    517517
    518           IF ( building_wall_left == 9999999.9 )  THEN
     518          IF ( building_wall_left == 9999999.9_wp )  THEN
    519519             building_wall_left = ( nx + 1 - blx ) / 2 * dx
    520520          ENDIF
     
    522522          bxr = bxl + blx
    523523
    524           IF ( building_wall_south == 9999999.9 )  THEN
     524          IF ( building_wall_south == 9999999.9_wp )  THEN
    525525             building_wall_south = ( ny + 1 - bly ) / 2 * dy
    526526          ENDIF
     
    547547!--       Single quasi-2D street canyon of infinite length in x or y direction.
    548548!--       The canyon is centered in the other direction by default.
    549           IF ( canyon_width_x /= 9999999.9 )  THEN
     549          IF ( canyon_width_x /= 9999999.9_wp )  THEN
    550550!
    551551!--          Street canyon in y direction
    552552             cwx = NINT( canyon_width_x / dx )
    553              IF ( canyon_wall_left == 9999999.9 )  THEN
     553             IF ( canyon_wall_left == 9999999.9_wp )  THEN
    554554                canyon_wall_left = ( nx + 1 - cwx ) / 2 * dx
    555555             ENDIF
     
    557557             cxr = cxl + cwx
    558558
    559           ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
     559          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
    560560!
    561561!--          Street canyon in x direction
    562562             cwy = NINT( canyon_width_y / dy )
    563              IF ( canyon_wall_south == 9999999.9 )  THEN
     563             IF ( canyon_wall_south == 9999999.9_wp )  THEN
    564564                canyon_wall_south = ( ny + 1 - cwy ) / 2 * dy
    565565             ENDIF
     
    578578!
    579579!--       Street canyon size has to meet some requirements
    580           IF ( canyon_width_x /= 9999999.9 )  THEN
     580          IF ( canyon_width_x /= 9999999.9_wp )  THEN
    581581             IF ( ( cxl < 1 ) .OR. ( cxr > nx-1 ) .OR. ( cwx < 3 ) .OR.  &
    582582               ( ch < 3 ) )  THEN
     
    587587                CALL message( 'init_grid', 'PA0205', 1, 2, 0, 6, 0 )
    588588             ENDIF
    589           ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
     589          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
    590590             IF ( ( cys < 1 ) .OR. ( cyn > ny-1 ) .OR. ( cwy < 3 ) .OR.  &
    591591               ( ch < 3 ) )  THEN
     
    597597             ENDIF
    598598          ENDIF
    599           IF ( canyon_width_x /= 9999999.9 .AND. canyon_width_y /= 9999999.9 ) &
     599          IF ( canyon_width_x /= 9999999.9_wp .AND. canyon_width_y /= 9999999.9_wp ) &
    600600               THEN
    601601             message_string = 'inconsistent canyon parameters:' //     & 
     
    606606
    607607          nzb_local = ch
    608           IF ( canyon_width_x /= 9999999.9 )  THEN
     608          IF ( canyon_width_x /= 9999999.9_wp )  THEN
    609609             nzb_local(:,cxl+1:cxr-1) = 0
    610           ELSEIF ( canyon_width_y /= 9999999.9 )  THEN
     610          ELSEIF ( canyon_width_y /= 9999999.9_wp )  THEN
    611611             nzb_local(cys+1:cyn-1,:) = 0
    612612          ENDIF
Note: See TracChangeset for help on using the changeset viewer.