[2452] | 1 | module disvert_icosa_lmdz_mod |
---|
| 2 | |
---|
| 3 | implicit none |
---|
| 4 | |
---|
| 5 | contains |
---|
| 6 | |
---|
| 7 | SUBROUTINE disvert_icosa_lmdz(ap,bp,presnivs) |
---|
| 8 | ! Routine to compute ap(),bp() and presnivs() in the same way as done |
---|
| 9 | ! in LMDZ for planets (see LMDZ.COMMON/libf/dyn3d_common/disvert_noterre.F) |
---|
| 10 | |
---|
| 11 | USE prec, ONLY : rstd |
---|
| 12 | USE getin_mod, ONLY : getin |
---|
| 13 | USE grid_param, ONLY: llm |
---|
| 14 | USE earth_const, ONLY: pa,preff,scale_height |
---|
| 15 | USE abort_mod, ONLY: dynamico_abort |
---|
| 16 | USE mpipara, ONLY: is_mpi_root |
---|
| 17 | USE omp_para, ONLY: omp_in_parallel |
---|
| 18 | USE transfert_omp_mod, ONLY: bcast_omp |
---|
| 19 | USE free_unit_mod, ONLY : free_unit |
---|
| 20 | IMPLICIT NONE |
---|
| 21 | |
---|
| 22 | REAL(rstd),INTENT(OUT) :: ap(:) |
---|
| 23 | REAL(rstd),INTENT(OUT) :: bp(:) |
---|
| 24 | REAL(rstd),INTENT(OUT) :: presnivs(:) |
---|
| 25 | |
---|
| 26 | INTEGER :: unit |
---|
| 27 | CHARACTER(len=255) :: filename |
---|
| 28 | INTEGER :: l,ok |
---|
| 29 | LOGICAL :: hybrid |
---|
| 30 | REAL(rstd) :: scaleheight ! atmospheric scale height (km) from file z2sig.def |
---|
| 31 | REAL(rstd) :: zsig(llm) |
---|
| 32 | REAL(rstd) :: sig(llm+1) |
---|
| 33 | REAL(rstd) :: newsig |
---|
| 34 | |
---|
| 35 | filename="z2sig.def" !file to read |
---|
| 36 | |
---|
| 37 | ! User may choose between hybrid (default) or sigma coordinates |
---|
| 38 | hybrid=.true. ! default: use hybrid coordinates |
---|
| 39 | CALL getin('hybrid',hybrid) |
---|
| 40 | ! User must also provide "pa" if in hybrid case |
---|
| 41 | if (hybrid) then |
---|
| 42 | pa=-999 ! absurd initial value to trigger error if not set |
---|
| 43 | CALL getin('pa',pa) |
---|
| 44 | IF (pa<0) THEN |
---|
| 45 | WRITE(*,*) "disvert_icosa_lmdz error: pa=",pa |
---|
| 46 | WRITE(*,*) " set a correct value for the pa parameter" |
---|
| 47 | CALL dynamico_abort("disvert_icosa_lmdz : wrong value for pa") |
---|
| 48 | ENDIF |
---|
| 49 | endif |
---|
| 50 | |
---|
| 51 | !$OMP MASTER |
---|
| 52 | unit=free_unit() |
---|
| 53 | OPEN(unit,file=filename,status="old",action="read",iostat=ok) |
---|
| 54 | IF (ok/=0) THEN |
---|
| 55 | WRITE(*,*) "disvert_icosa_lmdz error: input file ",trim(filename)," not found!" |
---|
| 56 | CALL dynamico_abort("disvert_icosa_lmdz : could not open z2sig.def file" ) |
---|
| 57 | ENDIF |
---|
| 58 | ! read "scaleheight" on the first line |
---|
| 59 | READ(unit,fmt=*,iostat=ok) scaleheight |
---|
| 60 | IF (ok/=0) THEN |
---|
| 61 | WRITE(*,*) "disvert_icosa_lmdz error: failed reading scaleheight" |
---|
| 62 | CALL dynamico_abort("disvert_icosa_lmdz : could not read input file") |
---|
| 63 | ENDIF |
---|
| 64 | ! While at it check that this "scaleheight" matches the "scale_height" |
---|
| 65 | ! from the def files |
---|
| 66 | IF ((1.-(scaleheight*1000.)/scale_height)>1.e-6) THEN |
---|
| 67 | WRITE(*,*) "disvert_icosa_lmdz error: significant mismatch between" |
---|
| 68 | WRITE(*,*) " scale_height (m) from def file:",scale_height |
---|
| 69 | WRITE(*,*) " and scaleheight (km) from z2sig.def:",scaleheight |
---|
| 70 | CALL dynamico_abort("disvert_icosa_lmdz : atmospheric scale height issue") |
---|
| 71 | ENDIF |
---|
| 72 | ! read zsig() line by line, starting from the surface up to model top |
---|
| 73 | DO l=1,llm |
---|
| 74 | READ(unit,fmt=*,iostat=ok) zsig(l) |
---|
| 75 | IF (ok/=0) THEN |
---|
| 76 | WRITE(*,*) "disvert_icosa_lmdz error: failed reading zsig(l) for l=",l |
---|
| 77 | CALL dynamico_abort("disvert_icosa_lmdz : could not read input file" ) |
---|
| 78 | ENDIF |
---|
| 79 | ENDDO |
---|
| 80 | CLOSE(unit) |
---|
| 81 | |
---|
| 82 | ! build sig() |
---|
| 83 | sig(1)=1. |
---|
| 84 | DO l=2,llm |
---|
| 85 | sig(l)=0.5*(exp(-zsig(l)/scaleheight)+exp(-zsig(l-1)/scaleheight)) |
---|
| 86 | ENDDO |
---|
| 87 | sig(llm+1)=0 ! here we asume 0 pressure at top of atmosphere |
---|
| 88 | |
---|
| 89 | ! build ap() and bp() using sig(), pa and preff |
---|
| 90 | IF (hybrid) THEN ! use hybrid coordinates |
---|
| 91 | DO l=1,llm |
---|
| 92 | CALL sig_hybrid(sig(l),pa,preff,newsig) |
---|
| 93 | bp(l)=exp(1.-1./(newsig**2)) |
---|
| 94 | ap(l)=pa*(newsig-bp(l)) |
---|
| 95 | ENDDO |
---|
| 96 | ELSE ! use sigma coordinates |
---|
| 97 | ap(1:llm)=0 |
---|
| 98 | bp(1:llm)=sig(1:llm) |
---|
| 99 | ENDIF |
---|
| 100 | ap(llm+1)=0 |
---|
| 101 | bp(llm+1)=0 |
---|
| 102 | !$OMP END MASTER |
---|
| 103 | |
---|
| 104 | IF (omp_in_parallel()) THEN |
---|
| 105 | CALL bcast_omp(ap) |
---|
| 106 | CALL bcast_omp(bp) |
---|
| 107 | ENDIF |
---|
| 108 | |
---|
| 109 | ! build presnivs(), approximative mid-layer pressures |
---|
| 110 | DO l=1,llm |
---|
| 111 | presnivs(l)=0.5*(ap(l)+bp(l)*preff+ap(l+1)+bp(l+1)*preff) |
---|
| 112 | ENDDO |
---|
| 113 | |
---|
| 114 | ! tell the world about it |
---|
| 115 | IF (is_mpi_root) THEN |
---|
| 116 | !$OMP MASTER |
---|
| 117 | WRITE(*,*) "Vertical discretization set by disvert_icosa_lmdz with hybrid=",hybrid |
---|
| 118 | WRITE(*,*) "ap()=",ap |
---|
| 119 | WRITE(*,*) "bp()=",bp |
---|
| 120 | WRITE(*,*) "Approximative mid-layer pressure, assuming a surface pressure preff=",preff," Pa" |
---|
| 121 | WRITE(*,*) "and approximative mid-layer height, assuming an atmospheric scale height of ",scale_height/1000," (km)" |
---|
| 122 | DO l=1,llm |
---|
| 123 | WRITE(*,*) 'PRESNIVS(',l,')=',presnivs(l),' Z ~ ',log(preff/presnivs(l))*scale_height/1000, & |
---|
| 124 | ' DZ ~ ',scale_height/1000*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10)) |
---|
| 125 | ENDDO |
---|
| 126 | !$OMP END MASTER |
---|
| 127 | ENDIF |
---|
| 128 | |
---|
| 129 | CONTAINS |
---|
| 130 | |
---|
| 131 | SUBROUTINE sig_hybrid(sig,pa,preff,newsig) |
---|
| 132 | ! F. Forget 2002 |
---|
| 133 | ! Iterative procedure to find "newsig" the sigma value for a layer |
---|
| 134 | ! based on the target values provided in z2sig.def (sig) |
---|
| 135 | ! but such that: |
---|
| 136 | ! (1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig = sig |
---|
| 137 | ! iterative solving of the equation uses the fact that: |
---|
| 138 | ! where exp(1-1./x**2) become << x |
---|
| 139 | ! x exp(1-1./x**2)/x |
---|
| 140 | ! 1 1 |
---|
| 141 | ! 0.68 0.5 |
---|
| 142 | ! 0.5 1.E-1 |
---|
| 143 | ! 0.391 1.E-2 |
---|
| 144 | ! 0.333 1.E-3 |
---|
| 145 | ! 0.295 1.E-4 |
---|
| 146 | ! 0.269 1.E-5 |
---|
| 147 | ! 0.248 1.E-6 |
---|
| 148 | ! => thus on can assume newsig = sig*preff/pa if sig*preff/pa < 0.25 |
---|
| 149 | |
---|
| 150 | IMPLICIT NONE |
---|
| 151 | REAL(rstd),INTENT(in) :: sig |
---|
| 152 | REAL(rstd),INTENT(in) :: pa |
---|
| 153 | REAL(rstd),INTENT(in) :: preff |
---|
| 154 | REAL(rstd),INTENT(out) :: newsig |
---|
| 155 | REAL(rstd) :: F,x1,x2 |
---|
| 156 | INTEGER :: j |
---|
| 157 | |
---|
| 158 | newsig=sig |
---|
| 159 | x1=0 |
---|
| 160 | x2=1 |
---|
| 161 | IF (sig.ge.1) THEN ! handle sigma=1 case |
---|
| 162 | newsig=sig |
---|
| 163 | ELSE IF (sig*preff/pa.ge.0.25) THEN |
---|
| 164 | DO J=1,9999 ! Overkill max number of iterations |
---|
| 165 | F=((1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig)/sig |
---|
| 166 | IF (F.gt.1) THEN |
---|
| 167 | x2=newsig |
---|
| 168 | newsig=(x1+newsig)*0.5 |
---|
| 169 | ELSE |
---|
| 170 | x1=newsig |
---|
| 171 | newsig=(x2+newsig)*0.5 |
---|
| 172 | ENDIF |
---|
| 173 | ! Convergence test: stop if sig is approximated to within 0.01m |
---|
| 174 | IF (abs(10.*log(F)).LT.1.E-5) EXIT |
---|
| 175 | ENDDO |
---|
| 176 | ELSE ! IF (sig*preff/pa.le.0.25) THEN |
---|
| 177 | newsig=sig*preff/pa |
---|
| 178 | ENDIF |
---|
| 179 | END SUBROUTINE sig_hybrid |
---|
| 180 | |
---|
| 181 | END SUBROUTINE disvert_icosa_lmdz |
---|
| 182 | |
---|
| 183 | |
---|
| 184 | end module disvert_icosa_lmdz_mod |
---|