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

Last change on this file since 196 was 186, checked in by ymipsl, 10 years ago

Add new openMP parallelism based on distribution of domains on threads. There is no more limitation of number of threads by MPI process.

YM

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