source: codes/icosagcm/trunk/src/disvert_dcmip3.f90 @ 186

Last change on this file since 186 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: 2.0 KB
Line 
1  MODULE disvert_dcmip31_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
14  SUBROUTINE init_disvert
15  USE icosa
16  IMPLICIT NONE
17 
18    ALLOCATE(ap(llm+1))
19    ALLOCATE(bp(llm+1))
20    ALLOCATE(presnivs(llm))
21   
22    CALL disvert(ap,bp,presnivs)   
23
24  END SUBROUTINE init_disvert 
25
26  SUBROUTINE disvert(ap,bp,presnivs)
27  USE icosa
28  USE mpipara
29  IMPLICIT NONE
30  REAL(rstd),INTENT(OUT) :: ap(:)
31  REAL(rstd),INTENT(OUT) :: bp(:)
32  REAL(rstd),INTENT(OUT) :: presnivs(:)
33  ! reads from run.def : ncar_dz, ncar_T0, ncar_p0, ncar_disvert_c
34  INTEGER :: l,cindx
35  REAL(rstd) :: GG, eta_top, eta
36  REAL(rstd),PARAMETER :: N=0.01         ! Brunt-Vaisala frequency (s-1)
37  REAL(rstd),PARAMETER :: Teq=300.       ! Surface temperature at the equator (K)
38  REAL(rstd),PARAMETER :: Peq=1e5        ! Reference surface pressure at the equator (hPa)
39
40  ncar_dz=400 ; CALL getin('ncar_dz',ncar_dz);
41  cindx=1 ; CALL getin('ncar_disvert_c',cindx)
42
43  GG=(g/N)**2/cpp
44 
45  eta_top = (GG/Teq*exp(-N**2*llm*ncar_dz/g)+1-GG/Teq)**(1./kappa)
46  IF (is_mpi_root) PRINT *,'eta_top ->', eta_top
47  do l = 1,llm+1
48     eta = (GG/Teq*exp(-N**2*(l-1)*ncar_dz/g)+1-GG/Teq)**(1./kappa)
49     IF (is_mpi_root) PRINT *,'eta ->', eta
50     bp(l) = ((eta - eta_top)/(1 - eta_top))**cindx
51     ap(l) = preff * ( eta - bp(l) )
52  ENDDO
53  IF (is_mpi_root) PRINT *,'eta ->', eta
54  bp(1)=1.
55  ap(1)=0.
56  bp(llm+1) = 0
57 
58  DO l = 1, llm
59     presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
60  ENDDO
61
62  IF (is_mpi_root) PRINT *, 'Vertical placement of model levels according to DCMIP Appendix E.3'
63  IF (is_mpi_root) PRINT *, 'Parameters : ncar_dz=', ncar_dz, '  ncar_p0=',ncar_p0, '  ncar_disvert_c=',cindx
64  IF (is_mpi_root) PRINT *, 'Isothermal amtosphere with ncar_T0=',ncar_T0 
65
66END SUBROUTINE disvert
67
68END  MODULE disvert_dcmip31_mod
Note: See TracBrowser for help on using the repository browser.