source: trunk/MESOSCALE_DEV/SRC/ARWpost/src/module_calc_rh.f90 @ 524

Last change on this file since 524 was 207, checked in by aslmd, 14 years ago

MESOSCALE: A GENERAL CLEAN-UP FOLLOWING UPDATING THE USER MANUAL. EVERYTHING ESSENTIAL IS IN MESOSCALE (much lighter than before). EVERYTHING FOR DEVELOPPERS OR EXPERTS IS IN MESOSCALE_DEV.

File size: 734 bytes
Line 
1!! Diagnostics: Relative Humidity
2
3MODULE module_calc_rh
4
5  CONTAINS
6  SUBROUTINE calc_rh(SCR, cname, cdesc, cunits)
7
8  USE constants_module
9  USE module_model_basics
10
11  !Arguments
12  real, pointer, dimension(:,:,:)                                :: SCR
13  character (len=128)                                            :: cname, cdesc, cunits
14
15  !Local
16  real, dimension(west_east_dim,south_north_dim,bottom_top_dim)  :: tmp1, tmp2 
17 
18
19  tmp1     = 10.*0.6112*exp(17.67*(TK-T0)/(TK-29.65))
20  tmp2     = EPS*tmp1/(0.01 * PRES -  (1.-EPS)*tmp1)
21  tmp1     = 100.*AMAX1(AMIN1(QV/tmp2,1.0),0.0)
22
23  SCR      = tmp1
24  cname    = "rh"
25  cdesc    = "Relative Humidity"
26  cunits   = "%"
27 
28  END SUBROUTINE calc_rh
29
30END MODULE module_calc_rh
Note: See TracBrowser for help on using the repository browser.