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/init_cloud_physics.f90

    r1335 r1353  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! REAL constants provided with KIND-attribute
    2323!
    2424! Former revisions:
     
    9393    REAL(wp) ::  t_surface  !:
    9494
    95     ALLOCATE( hyp(nzb:nzt+1), pt_d_t(nzb:nzt+1), t_d_pt(nzb:nzt+1),  &
     95    ALLOCATE( hyp(nzb:nzt+1), pt_d_t(nzb:nzt+1), t_d_pt(nzb:nzt+1),            &
    9696              hyrho(nzb:nzt+1) )
    9797
     
    104104    schmidt_p_1d3 = schmidt**( 1.0_wp / 3.0_wp )
    105105
    106     pirho_l  = pi * rho_l / 6.0
    107     dpirho_l = 1.0 / pirho_l
     106    pirho_l  = pi * rho_l / 6.0_wp
     107    dpirho_l = 1.0_wp / pirho_l
    108108!
    109109!-- Calculate timestep according to precipitation
    110110    IF ( icloud_scheme == 0  .AND.  precipitation )  THEN
    111        dt_precipitation = c_sedimentation * MINVAL( dzu(nzb+2:nzt) ) /        &
     111       dt_precipitation = c_sedimentation * MINVAL( dzu(nzb+2:nzt) ) /         &
    112112                          w_precipitation
    113113    ENDIF
    114114!
    115115!-- Calculate factor used in equation for droplet growth by condensation
    116     bfactor = 3.0 * vanthoff * mass_of_solute * molecular_weight_of_water &
    117               / ( 4.0 * pi * rho_l * molecular_weight_of_solute )
     116    bfactor = 3.0_wp * vanthoff * mass_of_solute * molecular_weight_of_water  &
     117              / ( 4.0_wp * pi * rho_l * molecular_weight_of_solute )
    118118!
    119119!-- Calculate:
     
    121121!-- t / pt : ratio of actual and potential temperature (t_d_pt)
    122122!-- p_0(z) : vertical profile of the hydrostatic pressure (hyp)
    123     t_surface = pt_surface * ( surface_pressure / 1000.0 )**0.286_wp
     123    t_surface = pt_surface * ( surface_pressure / 1000.0_wp )**0.286_wp
    124124    DO  k = nzb, nzt+1
    125125!
    126126!--    Check temperature in case of too large domain height
    127        IF ( ( t_surface - g/cp * zu(k) ) < 0.0 )  THEN
     127       IF ( ( t_surface - g/cp * zu(k) ) < 0.0_wp )  THEN
    128128          WRITE( message_string, * )  'absolute temperature < 0.0 at zu(', k, &
    129129                                      ') = ', zu(k)
    130130          CALL message( 'init_cloud_physics', 'PA0142', 1, 2, 0, 6, 0 )
    131131       ENDIF
    132        hyp(k)    = surface_pressure * 100.0 * &
     132       hyp(k)    = surface_pressure * 100.0_wp * &
    133133                   ( (t_surface - g/cp * zu(k)) / t_surface )**(1.0_wp/0.286_wp)
    134        pt_d_t(k) = ( 100000.0 / hyp(k) )**0.286_wp
    135        t_d_pt(k) = 1.0 / pt_d_t(k)
     134       pt_d_t(k) = ( 100000.0_wp / hyp(k) )**0.286_wp
     135       t_d_pt(k) = 1.0_wp / pt_d_t(k)
    136136       hyrho(k)  = hyp(k) / ( r_d * t_d_pt(k) * pt_init(k) )       
    137137    ENDDO
     
    139139!
    140140!-- Compute reference density
    141     rho_surface = surface_pressure * 100.0 / ( r_d * t_surface )
     141    rho_surface = surface_pressure * 100.0_wp / ( r_d * t_surface )
    142142
    143143
Note: See TracChangeset for help on using the changeset viewer.