source: trunk/MESOSCALE_DEV/SRC/ARWpost/src/module_pressure.f90_orig @ 207

Last change on this file since 207 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: 1.7 KB
Line 
1!! Calculate pressure (Pa) from MU and MUB (wrfinput data)
2
3MODULE module_pressure
4
5  CONTAINS
6  SUBROUTINE pressure(prs)
7
8  USE module_model_basics
9
10  !Arguments
11  real, pointer, dimension(:,:,:)       :: prs
12  real, dimension(bottom_top_dim)       :: rdnw, rdn
13  real                                  :: dnw, dn
14  real                                  :: qvf1, qvf2
15  real                                  :: p_base
16  integer                               :: i, j, k
17   
18
19  NULLIFY (prs)
20  ALLOCATE(prs(west_east_dim,south_north_dim,bottom_top_dim))
21
22
23
24     DO k = 1 , bottom_top_dim
25        dnw=(ZNW(k+1) - ZNW(k))
26        rdnw(k) = 1./dnw
27     END DO
28     DO k = 1 , bottom_top_dim
29        dn=.5 * ( 1./rdnw(k+1) + 1./rdnw(k))
30        rdn(k)=1./dn
31     END DO
32
33
34
35     DO j = 1 , south_north_dim
36     DO i = 1 , west_east_dim
37
38!      Get pressure perturbation at model top
39       k = bottom_top_dim 
40       qvf1 = QV(i,j,k) * .001
41       qvf2 = 1. / (1.+qvf1)
42       qvf1 = qvf1 * qvf2
43       prs(i,j,k) = - 0.5 * ( MU(i,j) + qvf1*MUB(i,j) ) / rdnw(k) / qvf2
44
45
46
47
48!      Now get pressure perturbation at levels below
49       DO k = 1 , bottom_top_dim-1
50          qvf1 = 0.5 * (QV(i,j,k)+QV(i,j,k+1)) * .001
51          qvf2 = 1. / (1.+qvf1)
52          qvf1 = qvf1 * qvf2
53          prs(i,j,k) = prs(i,j,k+1) - ( MU(i,j) + qvf1*MUB(i,j) ) / qvf2 / rdn(k)
54       END DO
55
56
57!      Finally compute base state pressure and add to pressure perturbation
58!      to get total pressure
59       DO k = 1 , bottom_top_dim
60          p_base = ZNU(k) * MUB(i,j) + PTOP
61          prs(i,j,k) =  prs(i,j,k) + p_base     ! Pa
62       END DO
63
64     END DO
65     END DO
66
67
68  END SUBROUTINE pressure
69
70END MODULE module_pressure
Note: See TracBrowser for help on using the repository browser.