source: codes/icosagcm/trunk/src/disvert_ncar.f90 @ 19

Last change on this file since 19 was 19, checked in by ymipsl, 12 years ago

Simplify the management of the module.

YM

File size: 1.3 KB
Line 
1  MODULE disvert_ncar_mod
2  USE icosa
3 
4  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: ap(:)
5  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: bp(:)
6  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: presnivs(:)
7
8CONTAINS 
9!=========================================================================
10
11  SUBROUTINE init_disvert
12  USE icosa
13  IMPLICIT NONE
14 
15    ALLOCATE(ap(llm+1))
16    ALLOCATE(bp(llm+1))
17    ALLOCATE(presnivs(llm))
18   
19    CALL disvert(ap,bp,presnivs)   
20
21  END SUBROUTINE init_disvert 
22
23
24  SUBROUTINE disvert(ap,bp,presnivs)
25  USE icosa
26  IMPLICIT NONE
27  REAL(rstd),INTENT(OUT) :: ap(:)
28  REAL(rstd),INTENT(OUT) :: bp(:)
29  REAL(rstd),INTENT(OUT) :: presnivs(:)
30 
31  REAL(rstd) :: sig(llm+1)
32  REAL(rstd) :: sigtop
33  REAL(rstd),PARAMETER:: p0=100000.0 
34  INTEGER :: l,cindx
35  REAL(rstd) :: hdz, ehdz 
36
37
38         hdz = 400.*g/(300.*287.) 
39         ehdz = exp(-hdz) 
40
41    do l = 1,llm+1
42        sig(l) = ehdz**(l-1) 
43    end do 
44       
45       sigtop = sig(llm+1) 
46        cindx = 1 
47
48    bp(llm+1) =   0.
49    DO l = 1, llm
50      bp(l) = (sig(l) - sigtop)/(1 - sigtop)
51      bp(l) = bp(l)**cindx
52      ap(l) = p0 * ( sig(l) - bp(l) )
53    ENDDO
54    bp(1)=1.
55    ap(1)=0.
56    ap(llm+1) = p0 * ( sig(llm+1) - bp(llm+1) )
57 
58    DO l = 1, llm
59      presnivs(l) = 0.5 *( ap(l)+bp(l)*p0 + ap(l+1)+bp(l+1)*p0 )
60   ENDDO
61
62  END SUBROUTINE disvert
63
64END  MODULE disvert_ncar_mod
Note: See TracBrowser for help on using the repository browser.