source: codes/icosagcm/trunk/src/disvert_std.f90 @ 208

Last change on this file since 208 was 208, checked in by ymipsl, 10 years ago

Atmosphere scaleheight is not hard coded in disvert_std, and given in meters instead km
YM

File size: 2.0 KB
Line 
1MODULE disvert_std_mod
2  USE icosa
3  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: ap(:)
4!$OMP THREADPRIVATE(ap)
5  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: bp(:)
6!$OMP THREADPRIVATE(bp)
7  REAL(rstd), SAVE, ALLOCATABLE,TARGET :: presnivs(:)
8!$OMP THREADPRIVATE(presnivs)
9
10CONTAINS
11
12  SUBROUTINE init_disvert
13  USE icosa
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
25  SUBROUTINE disvert(ap,bp,presnivs)
26  USE icosa
27  USE mpipara
28  USE earth_const
29  IMPLICIT NONE
30  REAL(rstd),INTENT(OUT) :: ap(:)
31  REAL(rstd),INTENT(OUT) :: bp(:)
32  REAL(rstd),INTENT(OUT) :: presnivs(:)
33 
34  REAL(rstd) :: dsig(llm)
35  REAL(rstd) :: sig(llm+1)
36  REAL(rstd) :: snorm
37  INTEGER :: l
38 
39    snorm  = 0.
40    DO l = 1, llm
41      dsig(l) = 1.0 + 7.0 * SIN( Pi*(l-0.5)/(llm+1) )**2
42      snorm = snorm + dsig(l)
43    ENDDO   
44   
45    DO l = 1, llm
46      dsig(l) = dsig(l)/snorm
47    ENDDO
48
49    sig(llm+1) = 0.
50    DO l = llm, 1, -1
51      sig(l) = sig(l+1) + dsig(l)
52    ENDDO
53
54    bp(llm+1) =   0.
55    DO l = 1, llm
56      bp(l) = EXP( 1. -1./( sig(l)*sig(l)) )
57      ap(l) = pa * ( sig(l) - bp(l) )
58    ENDDO
59    bp(1)=1.
60    ap(1)=0.
61    ap(llm+1) = pa * ( sig(llm+1) - bp(llm+1) )
62    DO l = 1, llm
63      presnivs(l) = 0.5 *( ap(l)+bp(l)*preff + ap(l+1)+bp(l+1)*preff )
64    ENDDO
65   
66    ! tell the world about it
67    IF (is_mpi_root) THEN
68!$OMP MASTER
69      WRITE(*,*) "ap()=",ap
70      WRITE(*,*) "bp()=",bp
71      WRITE(*,*) "Approximative mid-layer pressure, assuming a surface pressure preff=",preff," Pa"
72      WRITE(*,*) "and approximative mid-layer height, assuming an atmospheric scale height of ",scaleheight/1000," (km)"
73      DO l=1,llm
74        WRITE(*,*) 'PRESNIVS(',l,')=',presnivs(l),'  Z ~ ',log(preff/presnivs(l))*scaleheight/1000,       &
75                   ' DZ ~ ',scaleheight/1000*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10))
76      ENDDO
77!$OMP END MASTER
78    ENDIF
79 
80  END SUBROUTINE disvert
81 
82END MODULE disvert_std_mod
Note: See TracBrowser for help on using the repository browser.