source: codes/icosagcm/trunk/src/disvert_ncarl30.f90 @ 78

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

bug fix for ncar vertical discretisation at 30 levels

YM

File size: 4.0 KB
Line 
1MODULE disvert_ncarl30_mod
2  USE icosa
3  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: ap(:)
4  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: bp(:)
5  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: presnivs(:)
6
7CONTAINS
8
9  SUBROUTINE init_disvert
10  USE icosa
11  IMPLICIT NONE
12 
13    IF (llm/=30) STOP 'ERROR, the initialisation of this vertical discretisation must be done with 30 levels'
14    ALLOCATE(ap(llm+1))
15    ALLOCATE(bp(llm+1))
16    ALLOCATE(presnivs(llm))
17
18    CALL disvert(ap,bp,presnivs)   
19
20  END SUBROUTINE init_disvert 
21
22
23  SUBROUTINE disvert(ap,bp,presnivs)
24  USE icosa
25  IMPLICIT NONE
26  REAL(rstd),INTENT(OUT) :: ap(:)
27  REAL(rstd),INTENT(OUT) :: bp(:)
28  REAL(rstd),INTENT(OUT) :: presnivs(:)
29  INTEGER :: l
30  REAL(rstd) :: a(31)=(/ 0.00225523952394724, &
31                         0.00503169186413288, &
32                         0.0101579474285245 , &
33                         0.0185553170740604 , &
34                         0.0306691229343414 , &
35                         0.0458674766123295 , &
36                         0.0633234828710556 , &
37                         0.0807014182209969 , &
38                         0.0949410423636436 , &
39                         0.11169321089983   , &
40                         0.131401270627975  , &
41                         0.154586806893349  , &
42                         0.181863352656364  , &
43                         0.17459799349308   , &
44                         0.166050657629967  , &
45                         0.155995160341263  , &
46                         0.14416541159153   , &
47                         0.130248308181763  , &
48                         0.113875567913055  , &
49                         0.0946138575673103 , &
50                         0.0753444507718086 , &
51                         0.0576589405536652 , &
52                         0.0427346378564835 , &
53                         0.0316426791250706 , &
54                         0.0252212174236774 , &
55                         0.0191967375576496 , &
56                         0.0136180268600583 , &
57                         0.00853108894079924, &
58                         0.00397881818935275, &
59                         0.                 , &
60                         0. /) 
61                         
62  REAL(rstd) :: b(31)=(/ 0.                 , &
63                         0.                 , &
64                         0.                 , &
65                         0.                 , &
66                         0.                 , &
67                         0.                 , &
68                         0.                 , &
69                         0.                 , &
70                         0.                 , &
71                         0.                 , &
72                         0.                 , &
73                         0.                 , &
74                         0.                 , &
75                         0.0393548272550106 , &
76                         0.0856537595391273 , &
77                         0.140122056007385  , &
78                         0.204201176762581  , &
79                         0.279586911201477  , &
80                         0.368274360895157  , &
81                         0.47261056303978   , &
82                         0.576988518238068  , &
83                         0.672786951065063  , &
84                         0.753628432750702  , &
85                         0.813710987567902  , &
86                         0.848494648933411  , &
87                         0.881127893924713  , &
88                         0.911346435546875  , &
89                         0.938901245594025  , &
90                         0.963559806346893  , &
91                         0.985112190246582  , &
92                         1. /)                         
93                   
94    ap(:)=a(31:1:-1)*preff
95    bp(:)=b(31:1:-1) 
96    DO l = 1, llm
97      presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
98 
99      PRINT*, 'PRESNIVS(',l,')=',presnivs(l),'  Z ~ ',log(preff/presnivs(l))*8.,       &
100              ' DZ ~ ',8.*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10))
101    ENDDO
102 
103  END SUBROUTINE disvert
104 
105END MODULE disvert_ncarl30_mod
Note: See TracBrowser for help on using the repository browser.