source: codes/icosagcm/trunk/src/vertical/disvert_dcmip3.f90 @ 606

Last change on this file since 606 was 548, checked in by dubos, 7 years ago

trunk : reorganize source tree

File size: 2.1 KB
RevLine 
[353]1MODULE disvert_dcmip31_mod
[115]2  USE icosa
[353]3  IMPLICIT NONE
4  PRIVATE
5
[115]6  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: ap(:)
[186]7!$OMP THREADPRIVATE(ap)
[115]8  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: bp(:)
[186]9!$OMP THREADPRIVATE(bp)
[115]10  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: presnivs(:)
[186]11!$OMP THREADPRIVATE(presnivs)
[115]12
[353]13  PUBLIC :: ap,bp,presnivs, init_disvert
14
[115]15CONTAINS
16!=========================================================================
17
18  SUBROUTINE init_disvert
19    ALLOCATE(ap(llm+1))
20    ALLOCATE(bp(llm+1))
21    ALLOCATE(presnivs(llm))
22    CALL disvert(ap,bp,presnivs)   
[353]23  END SUBROUTINE init_disvert
[115]24
25  SUBROUTINE disvert(ap,bp,presnivs)
[131]26  USE mpipara
[115]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) :: GG, eta_top, eta
33  REAL(rstd),PARAMETER :: N=0.01         ! Brunt-Vaisala frequency (s-1)
34  REAL(rstd),PARAMETER :: Teq=300.       ! Surface temperature at the equator (K)
35  REAL(rstd),PARAMETER :: Peq=1e5        ! Reference surface pressure at the equator (hPa)
36
37  ncar_dz=400 ; CALL getin('ncar_dz',ncar_dz);
38  cindx=1 ; CALL getin('ncar_disvert_c',cindx)
39
40  GG=(g/N)**2/cpp
41 
42  eta_top = (GG/Teq*exp(-N**2*llm*ncar_dz/g)+1-GG/Teq)**(1./kappa)
[131]43  IF (is_mpi_root) PRINT *,'eta_top ->', eta_top
[115]44  do l = 1,llm+1
45     eta = (GG/Teq*exp(-N**2*(l-1)*ncar_dz/g)+1-GG/Teq)**(1./kappa)
[131]46     IF (is_mpi_root) PRINT *,'eta ->', eta
[115]47     bp(l) = ((eta - eta_top)/(1 - eta_top))**cindx
48     ap(l) = preff * ( eta - bp(l) )
49  ENDDO
[131]50  IF (is_mpi_root) PRINT *,'eta ->', eta
[115]51  bp(1)=1.
52  ap(1)=0.
53  bp(llm+1) = 0
54 
55  DO l = 1, llm
56     presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
57  ENDDO
58
[209]59!$OMP MASTER 
[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
62  IF (is_mpi_root) PRINT *, 'Isothermal amtosphere with ncar_T0=',ncar_T0 
[209]63!$OMP END MASTER 
[115]64
65END SUBROUTINE disvert
66
67END  MODULE disvert_dcmip31_mod
Note: See TracBrowser for help on using the repository browser.