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

Last change on this file since 191 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: 1.8 KB
Line 
1  MODULE disvert_ncar_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) :: H, eta_top, eta
36
37  ncar_dz=400 ; CALL getin('ncar_dz',ncar_dz);
38
39! SELECT CASE(
40! pressure profile depends on test case
41! coded here for 1-x (transport)
42
43  ncar_T0=300; CALL getin('ncar_T0',ncar_T0)
44  ncar_p0=1e5; CALL getin('ncar_p0',ncar_p0)
45  cindx=1 ; CALL getin('ncar_disvert_c',cindx)
46
47  H = ncar_T0*cpp*kappa/g ! height scale R.T0/g with R=cpp*kappa
48  eta_top = exp(-llm*ncar_dz/H)
49 
50  do l = 1,llm+1
51     eta = exp(-(l-1)*ncar_dz/H)
52     bp(l) = ((eta - eta_top)/(1 - eta_top))**cindx
53     ap(l) = ncar_p0 * ( eta - bp(l) )
54  ENDDO
55  bp(1)=1.
56  ap(1)=0.
57  bp(llm+1) = 0
58 
59  DO l = 1, llm
60     presnivs(l) = 0.5 *( ap(l)+bp(l)*ncar_p0 + ap(l+1)+bp(l+1)*ncar_p0 )
61  ENDDO
62
63  IF (is_mpi_root) PRINT *, 'Vertical placement of model levels according to DCMIP Appendix E.3'
64  IF (is_mpi_root) PRINT *, 'Parameters : ncar_dz=', ncar_dz, '  ncar_p0=',ncar_p0, '  ncar_disvert_c=',cindx
65  PRINT *, 'Isothermal amtosphere with ncar_T0=',ncar_T0 
66
67END SUBROUTINE disvert
68
69END  MODULE disvert_ncar_mod
Note: See TracBrowser for help on using the repository browser.