Ignore:
Timestamp:
Oct 21, 2016 3:11:58 PM (8 years ago)
Author:
knoop
Message:

Renamed variable rho to rho_ocean, rho_init to rho_ocean_init and rho_av to rho_ocean_av

File:
1 edited

Legend:

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

    r2025 r2031  
    2121! Current revisions:
    2222! ------------------
    23 !
     23! renamed variable rho to rho_ocean
    2424!
    2525! Former revisions:
     
    419419    INTEGER(iwp), PARAMETER                        :: icsurf   = 5         !< Surface skin layer heat capacity (J m−2 K−1 )
    420420    INTEGER(iwp), PARAMETER                        :: ithick   = 6         !< thickness of the surface (wall, roof, land)  ( m )
    421     INTEGER(iwp), PARAMETER                        :: irhoC    = 7         !< volumetric heat capacity rho*C of the material ( J m−3 K−1 )
     421    INTEGER(iwp), PARAMETER                        :: irhoC    = 7         !< volumetric heat capacity rho_ocean*C of the material ( J m−3 K−1 )
    422422    INTEGER(iwp), PARAMETER                        :: ilambdah = 8         !< thermal conductivity λH of the wall (W m−1 K−1 )
    423423    CHARACTER(12), DIMENSION(:), ALLOCATABLE       :: surface_type_names   !< names of wall types (used only for reports)
     
    28862886        IF ( plant_canopy )  THEN
    28872887            pchf_prep(:) = r_d * (hyp(nzub:nzut) / 100000.0_wp)**0.286_wp &
    2888                         / (cp * hyp(nzub:nzut) * dx*dy*dz) !< equals to 1 / (rho * c_p * Vbox * T)
     2888                        / (cp * hyp(nzub:nzut) * dx*dy*dz) !< equals to 1 / (rho_ocean * c_p * Vbox * T)
    28892889        ENDIF
    28902890
     
    38633863            ENDIF
    38643864           
    3865 !--         volumetric heat capacity rho*C of the wall ( J m−3 K−1 )
     3865!--         volumetric heat capacity rho_ocean*C of the wall ( J m−3 K−1 )
    38663866            rho_c_wall(:,l) = surface_params(irhoC, ip)
    38673867           
     
    39303930            pt1  = pt(k,j,i)
    39313931
    3932 !--         calculate rho * cp coefficient at surface layer
     3932!--         calculate rho_ocean * cp coefficient at surface layer
    39333933            rho_cp  = cp * hyp(k) / ( r_d * pt1 * exn(k) )
    39343934
Note: See TracChangeset for help on using the changeset viewer.