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

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

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

YM

File size: 1.7 KB
Line 
1  MODULE disvert_ncar_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  IMPLICIT NONE
14 
15    ALLOCATE(ap(llm+1))
16    ALLOCATE(bp(llm+1))
17    ALLOCATE(presnivs(llm))
18   
19    CALL disvert(ap,bp,presnivs)   
20
21  END SUBROUTINE init_disvert 
22
23  SUBROUTINE disvert(ap,bp,presnivs)
24  USE icosa
25  USE mpipara
26  IMPLICIT NONE
27  REAL(rstd),INTENT(OUT) :: ap(:)
28  REAL(rstd),INTENT(OUT) :: bp(:)
29  REAL(rstd),INTENT(OUT) :: presnivs(:)
30  ! reads from run.def : ncar_dz, ncar_T0, ncar_p0, ncar_disvert_c
31  INTEGER :: l,cindx
32  REAL(rstd) :: H, eta_top, eta
33
34  ncar_dz=400 ; CALL getin('ncar_dz',ncar_dz);
35
36! SELECT CASE(
37! pressure profile depends on test case
38! coded here for 1-x (transport)
39
40  ncar_T0=300; CALL getin('ncar_T0',ncar_T0)
41  ncar_p0=1e5; CALL getin('ncar_p0',ncar_p0)
42  cindx=1 ; CALL getin('ncar_disvert_c',cindx)
43
44  H = ncar_T0*cpp*kappa/g ! height scale R.T0/g with R=cpp*kappa
45  eta_top = exp(-llm*ncar_dz/H)
46 
47  do l = 1,llm+1
48     eta = exp(-(l-1)*ncar_dz/H)
49     bp(l) = ((eta - eta_top)/(1 - eta_top))**cindx
50     ap(l) = ncar_p0 * ( 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)*ncar_p0 + ap(l+1)+bp(l+1)*ncar_p0 )
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  PRINT *, 'Isothermal amtosphere with ncar_T0=',ncar_T0 
63
64END SUBROUTINE disvert
65
66END  MODULE disvert_ncar_mod
Note: See TracBrowser for help on using the repository browser.