source: codes/icosagcm/trunk/src/disvert_ncar.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.7 KB
RevLine 
[17]1  MODULE disvert_ncar_mod
[19]2  USE icosa
[17]3 
4  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: ap(:)
5  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: bp(:)
6  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: presnivs(:)
7
[25]8CONTAINS
[17]9!=========================================================================
10
11  SUBROUTINE init_disvert
[19]12  USE icosa
[17]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)
[19]24  USE icosa
[131]25  USE mpipara
[17]26  IMPLICIT NONE
27  REAL(rstd),INTENT(OUT) :: ap(:)
28  REAL(rstd),INTENT(OUT) :: bp(:)
29  REAL(rstd),INTENT(OUT) :: presnivs(:)
[25]30  ! reads from run.def : ncar_dz, ncar_T0, ncar_p0, ncar_disvert_c
[17]31  INTEGER :: l,cindx
[25]32  REAL(rstd) :: H, eta_top, eta
[17]33
[25]34  ncar_dz=400 ; CALL getin('ncar_dz',ncar_dz);
[17]35
[25]36! SELECT CASE(
37! pressure profile depends on test case
38! coded here for 1-x (transport)
[17]39
[25]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)
[17]43
[25]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
[17]55 
[25]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
[17]59
[131]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
[25]62  PRINT *, 'Isothermal amtosphere with ncar_T0=',ncar_T0 
[17]63
[25]64END SUBROUTINE disvert
65
[17]66END  MODULE disvert_ncar_mod
Note: See TracBrowser for help on using the repository browser.