source: codes/icosagcm/trunk/src/disvert_dcmip200.f90 @ 167

Last change on this file since 167 was 131, checked in by ymipsl, 11 years ago

Some operations must be only done by the mpi master task.

YM

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