source: trunk/LMDZ.MARS/libf/phymars/elimin_mz1d.F @ 426

Last change on this file since 426 was 414, checked in by aslmd, 14 years ago

LMDZ.MARS : NEW NLTE MODEL FROM GRANADA AMIGOS

23/11/11 == FGG + MALV

New parameterization of the NLTE 15 micron cooling. The old parameterization is kept as an option, including or not variable atomic oxygen concentration. A new flag is introduced in callphys.def, nltemodel, to select which parameterization wants to be used (new one, old one with variable [O], or old one with fixed [O], see below). Includes many new subroutines and commons in phymars. Some existing routines are also modified:

-physiq.F. Call to the new subroutine NLTE_leedat in first call. Call to nltecool modified to allow for variable atomic oxygen. Depending on the value of nltemodel, the new subroutine NLTEdlvr09_TCOOL is called instead of nltecool.

-inifis.F. Reading of nltemodel is added.

-callkeys.h Declaration of nltemodel is added.

The following lines should be added to callphys.def (ideally after setting callnlte):

# NLTE 15um scheme to use.
# 0-> Old scheme, static oxygen
# 1-> Old scheme, dynamic oxygen
# 2-> New scheme
nltemodel = 2

A new directory, NLTEDAT, has to be included in datagcm.

Improvements into NLTE NIR heating parameterization to take into account variability with O/CO2 ratio and SZA. A new subroutine, NIR_leedat.F, and a new common, NIRdata.h, are included. A new flag, nircorr, is added in callphys.def, to include or not these corrections. The following files are modified:

-nirco2abs.F: nq and pq are added in the arguments. The corrections factors are interpolated to the GCM grid and included in the clculation. A new subroutine, interpnir, is added at the end of the file.

-physiq.F: Call to NIR_leedat added at first call. Modified call to nirco2abs

-inifis: Reading new flag nircorr.

-callkeys.h: Declaration of nircorr.

The following lines have to be added to callphys.def (ideally after callnirco2):

# NIR NLTE correction for variable SZA and O/CO2?
# matters only if callnirco2=T
# 0-> no correction
# 1-> include correction
nircorr=1

A new data file, NIRcorrection_feb2011.dat, has to be included in datagcm.

Small changes to the molecular diffusion scheme to fix the number of species considered, to avoid problems when compiling with more than 15 tracers (for example, when CH4 is included). Modified subroutines: aeronomars/moldiff.F and aeronomars/moldiffcoeff.F

File size: 7.3 KB
Line 
1c       ************************************************************************
2        subroutine elimin_mz1d (c,vc, ilayer,nan,itblout, nw)
3
4c       Eliminate anomalous negative numbers in c(nl,nl) according to "nan":
5
6c        nan = 0 -> no eliminate
7c              @       -> eliminate all numbers with absol.value<abs(max(c(n,r)))/300.
8c              2 -> eliminate all anomalous negative numbers in c(n,r).
9c              3 -> eliminate all anomalous negative numbers far from the main
10c                   diagonal.
11c              8 -> eliminate all non-zero numbers outside the main diagonal,
12c                   and the contibution of lower boundary.
13c              9 -> eliminate all non-zero numbers outside the main diagonal.
14c              4 -> hace un smoothing cuando la distancia de separacion entre
15c                   el valor maximo y el minimo de cf > 50 capas.
16c              5 -> elimina valores menores que 1.0d-19
17c              6 -> incluye los dos casos 4 y 5
18c              7 -> llama a lisa: smooth con width=nw & elimina mejorado
19c              78-> incluye los dos casos 7 y 8
20c              79-> incluye los dos casos 7 y 9
21
22c       itblout (itableout in calling program) is the option for writing
23c       out or not the purged c(n,r) matrix:
24c       itblout = 0 -> no write 
25c               = 1 -> write out in curtis***.out according to ilayer
26
27c       ilayer is the index for the layer selected to write out the matrix:
28c       ilayer = 0  => matrix elements written out cover all the altitudes
29c                                                     with 5 layers steps
30c              > 0  =>   "        "      "      "  are  c(ilayer,*)
31c       NOTA:
32c         EXISTE LA POSIBILIDAD DE SACAR TODAS LAS CAPAS (TODA LA MATRIZ)
33c         UTILIZANDO itableout=30 EN MZTUD
34
35c       jul 2011        malv+fgg       adapted to LMD-MGCM
36c       Sep-04          FGG+MALV        Correct include and call parameters
37c       cristina        25-sept-1996   y  27-ene-1997
38c       JAN 98          MALV            Version for mz1d
39c       ************************************************************************
40
41        implicit none
42
43        include 'nltedefs.h'
44
45        integer   nan,j,i,itblout,kk,k,ir,in
46        integer   ilayer,jmin, jmax,np,nw,ntimes,ntimes2
47!*      real*8    c(nl,nl), vc(nl), amax, cmax, cmin, cs(nl,nl), mini
48        real*8    c(nl,nl), vc(nl), amax, cmax, cmin, mini
49        real*8 aux(nl), auxs(nl)
50        character layercode*3
51
52        ntimes=0
53        ntimes2=0
54!       type *,'from elimin_mz4: nan, nw',nan,nw
55
56        if (nan .eq. 0) goto 200
57
58        if(nan.eq.1)then
59                do i=1,nl
60                        amax=1.0d-36
61                        do j=1,nl
62                          if(abs(c(i,j)).gt.amax)amax=abs(c(i,j))
63                        end do
64                        do j=1,nl
65                          if(abs(c(i,j)).lt.amax/300.0d0)c(i,j)=0.0d0
66                        end do
67                enddo
68        elseif(nan.eq.2)then
69                do i=1,nl
70                        do j=1,nl
71                          if( ( j.le.(i-2) .or. j.gt.(i+2) ).and.
72     @                    ( c(i,j).lt.0.0d0 ) ) c(i,j)=0.0d0
73                        end do
74                enddo
75        elseif(nan.eq.3)then
76                do i=1,nl
77                        do j=1,nl
78                            if (abs(i-j).ge.10) c(i,j)=0.0d0
79                        end do
80                enddo
81        elseif(nan.eq.8)then
82                do i=1,nl
83                        do j=1,i-1
84                                c(i,j)=0.0d0
85                        enddo
86                        do j=i+1,nl
87                                c(i,j)=0.0d0
88                        enddo
89                        vc(i)= 0.d0
90                enddo
91        elseif(nan.eq.9)then
92                do i=1,nl
93                        do j=1,i-1
94                                c(i,j)=0.0d0
95                        enddo
96                        do j=i+1,nl
97                                c(i,j)=0.0d0
98                        enddo
99                enddo
100!       elseif(nan.eq.7.or.nan.eq.78.or.nan.eq.79)then
101!               call lisa(c, vc, nl, nw)
102        end if
103        if(nan.eq.78)then
104                do i=1,nl
105                        do j=1,i-1
106                                c(i,j)=0.0d0
107                        enddo
108                        do j=i+1,nl
109                                c(i,j)=0.0d0
110                        enddo
111                        vc(i)= 0.d0
112                enddo
113        endif
114        if(nan.eq.79)then
115                do i=1,nl
116                        do j=1,i-1
117                                c(i,j)=0.0d0
118                        enddo
119                        do j=i+1,nl
120                                c(i,j)=0.0d0
121                        enddo
122                enddo
123        endif
124
125        if(nan.eq.5.or.nan.eq.6)then
126                do i=1,nl
127                        mini = 1.0d-19
128                        do j=1,nl
129                         if(abs(c(i,j)).le.mini.and.c(i,j).ne.0.d0) then
130                            ntimes2=ntimes2+1
131                         end if
132                           if ( abs(c(i,j)).le.mini) c(i,j)=0.d0
133                        end do
134                enddo
135        end if
136
137        if(nan.eq.4.or.nan.eq.6)then
138                do i=1,nl
139                        do j=1,nl
140                          aux(j)=c(i,j)
141                          auxs(j)=c(i,j)
142                        end do
143                        call maxdp_2(aux,nl,cmax,jmax)
144                           if(abs(jmax-i).ge.50) then
145                                call smooth_cf(aux,auxs,i,nl,3)
146                                !!!call smooth_cf(aux,auxs,i,nl,5)
147                                ntimes=ntimes+1
148                           end if
149                        do j=1,nl
150                          c(i,j)=auxs(j)
151                        end do
152                end do
153        end if
154
155!          type *, 'elimin_mz4: c(n,r) procesed for elimination. '
156!          type *, ' '
157!          if(nan.eq.4.or.nan.eq.6) type *, '    call smoothing:',ntimes
158!          if(nan.eq.5.or.nan.eq.6) type *, '    call elimina:  ',ntimes2
159!          if(nan.eq.7)   type *, '    from elimin: lisa w=',nw
160!          type *, ' '
161
162
163 200    continue
164
165c       writting out of c(n,r) in ascii file
166
167!       if(itblout.eq.1) then
168
169!         if (ilayer.eq.0) then
170
171!          open (unit=2, status='new',
172!     @    file=dircurtis//'curtis_gnu.out', recl=1024)
173!           write(2,'(a)')
174!     @    ' curtis matrix:     table with   1.e+7 * acf(n,r) '
175!           write(2,114) 'n,r', ( i, i=nl,1,-5 )
176!           do in=nl,1,-5
177!             write(2,*)
178!             write(2,115) in, ( c(in,ir)*1.d7, ir=nl,1,-5 )
179!           end do
180!          close(2)
181
182
183!          write (*,*)  ' '
184!          write (*,*)  '  curtis.out has been created. '
185!          write (*,*)  ' '
186
187!         else
188
189!            write (layercode,132) ilayer
190!           open (2, status='new',
191!     @    file=dircurtis//'curtis'//layercode//'.out')
192!           write(2,'(a)')
193!     @    ' curtis matrix:     table with   1.e+7 * acf(n,r) '
194!           write(2,116) ' layer x       c(',layercode,
195!     @    ',x)           c(x,', layercode,')'
196!           do in=nl,1,-1
197!            if (c(ilayer,ilayer).ne.0.d0) then
198!             write(2,117) in, c(ilayer,in), c(in,ilayer),
199!     @        c(ilayer,in)/c(ilayer,ilayer),
200!     @        c(in,ilayer)/c(ilayer,ilayer)
201!            else
202!             write(2,118) in, c(ilayer,in), c(in,ilayer)
203!            end if
204!           end do
205!           close(2)
206!           write (*,*)  ' '
207!           write (*,*)  dircurtis//'curtis'//layercode//'.out',
208!     @ ' has been created.'
209!           write (*,*) ' '
210
211!         end if
212
213!       elseif(itblout.eq.0)then
214
215!         continue
216
217!       else
218
219!         write (*,*) ' error from elimin: ',
220!     @      ' itblout should be 1 or 0;   itblout= ',itblout
221!         stop
222
223!       end if
224       
225        return
226
227112     format(10x,10(i3,9x))
228113     format(1x,i3,2x,9(1pe9.2,2x))
229
230114     format(1x,a3, 11(8x,i3))
231115     format( 1x,i3, 2x, 11(1pe10.3))
232116     format( 1x,a17,a2,a18,a2,a1 )
233117     format( 3x,i3, 4(8x,1pe10.3) )
234118     format( 3x,i3, 2(8x,1pe10.3) )
235120     format( 1x,i3, 1x,i3, 2x, 11(1pe10.3))
236
237132     format(i3)
238
239!  cambio: los formatos 114, 115 , 117 y 118
240!  cambio: al cambia nl de 51 a 140 hay que cambiar el formato i2-->i3
241!          y ahora en vez de 11 capas de 5 en 5, hay 28
242!
243        end
244c**************************************************************************
245        subroutine smooth_cf( c, cs, i, nl, w )
246c       hace un smoothing de c(i,*), de la contribucion de todas las capas
247c       menos de la capa en cuestion, la i.
248c       opcion w (width): el tamanho de la ventana del smoothing.
249c       output values: cs
250c**************************************************************************
251
252        implicit none
253
254        integer  j,np,i,nl,w
255        real*8   c(nl), cs(nl)
256
257        if(w.eq.0) then
258         do j=1,nl
259                cs(j)=c(j)
260         end do
261
262        elseif(w.eq.3) then
263
264!       write (*,*) 'smoothing w=3'
265         do j=1,i-4
266                   if(j.eq.1) then
267                        cs(j)=c(j)
268                   else
269                        cs(j)=1/3.d0*(c(j-1)+c(j)+c(j+1))
270                   end if
271         end do
272         do j=i+4,nl-1
273                   if(j.eq.nl) then
274                        cs(j)=c(j)
275                   else
276                        cs(j)=1/3.d0*(c(j-1)+c(j)+c(j+1))
277                   end if
278         end do
279        elseif(w.eq.5) then
280
281!       type *,'smoothing w=5'
282         do j=3,i-4
283                   if(j.eq.1) then
284                        cs(j)=c(j)
285                   else
286                        cs(j)=1/5.d0*(c(j-2)+c(j-1)+c(j)+c(j+1)+c(j+2))
287                   end if
288         end do
289         do j=i+4,nl-2
290                   if(j.eq.nl) then
291                        cs(j)=c(j)
292                   else
293                        cs(j)=1/5.d0*(c(j-2)+c(j-1)+c(j)+c(j+1)+c(j+2))
294                   end if
295         end do
296        end if
297        return
298        end
299
300
Note: See TracBrowser for help on using the repository browser.