source: trunk/LMDZ.MARS/libf/dyn3d/inidissip.F @ 1242

Last change on this file since 1242 was 1130, checked in by emillour, 11 years ago

Mars GCM:
Series of changes to enable running in parallel (using LMDZ.COMMON dynamics);
Current LMDZ.MARS can still notheless be compiled and run in serial mode
"as previously".
Summary of main changes:

  • Main programs (newstart, start2archive, xvik) that used to be in dyn3d have been moved to phymars.
  • dyn3d/control.h is now module control_mod.F90
  • rearanged input/outputs routines everywhere to handle serial/MPI cases. physdem.F => phyredem.F90 , phyetat0.F => phyetat0.F90 ; all read/write routines for startfi files are gathered in module iostart.F90
  • added parallelism related routines init_phys_lmdz.F90, comgeomphy.F90, dimphy.F90, iniphysiq.F90, mod_grid_phy_lmdz.F90, mod_phys_lmdz_mpi_data.F90, mod_phys_lmdz_mpi_transfert.F90, mod_phys_lmdz_omp_data.F90, mod_phys_lmdz_omp_transfert.F90, mod_phys_lmdz_para.F90, mod_phys_lmdz_transfert_para.F90 in phymars and mod_const_mpi.F90 in dyn3d (for compliance with parallel case)
  • created generic routines 'planetwide_maxval' and 'planetwide_minval', in module "planetwide_mod", that enable obtaining the min and max of a field over the whole planet.

EM

File size: 8.9 KB
Line 
1      SUBROUTINE inidissip ( lstardis,nitergdiv,nitergrot,niterh  ,
2     *                       tetagdiv,tetagrot,tetatemp             )
3c=======================================================================
4c   initialisation de la dissipation horizontale
5c=======================================================================
6c-----------------------------------------------------------------------
7c   declarations:
8c   -------------
9
10      use control_mod, only: idissip, iperiod
11      IMPLICIT NONE
12#include "dimensions.h"
13#include "paramet.h"
14#include "comdissipn.h"
15#include "comconst.h"
16#include "comvert.h"
17!#include "control.h"
18
19      LOGICAL lstardis
20      INTEGER nitergdiv,nitergrot,niterh
21      REAL    tetagdiv,tetagrot,tetatemp
22      REAL zvert(llm),zz
23      REAL zh(ip1jmp1),zu(ip1jmp1),zv(ip1jm),deltap(ip1jmp1,llm)
24      REAL ullm,vllm,umin,vmin,zhmin,zhmax
25      REAL zllm,z1llm
26
27      INTEGER l,ij,idum,ii
28      REAL tetamin
29
30      EXTERNAL ran1
31      REAL ran1
32      real sig_s(llm)
33      save sig_s
34      logical firstcall
35      data firstcall/.true./
36      save firstcall
37
38      REAL fac_mid
39      REAL fac_up
40      REAL delta
41      REAL middle,startalt
42      SAVE fac_mid, fac_up, delta, startalt, middle
43
44c ------------------------------------------------------
45      if (firstcall) then
46         firstcall=.false.
47         do l=1,llm
48            sig_s(l)=aps(l)/preff + bps(l)
49         enddo
50
51c        COMPUTING THE VARIATION OF DISSIPATION AS A FUNCTION OF MODEL TOP :
52c         FF 2004       
53         if (pseudoalt(llm).lt.160.) then
54             fac_mid=3  ! coeff  pour dissipation aux basses/moyennes altitudes
55             fac_up=30 ! coeff multiplicateur pour dissipation hautes altitudes
56             startalt=70. ! altitude en Km de la transition mid / up
57             delta=20.! Intervalle (km) pour le changement mid / up
58         else ! thermosphere model
59             fac_mid=3 ! coeff pour dissipation aux basses/moyennes altitudes
60             fac_up=30 ! coeff multiplicateur pour dissipation hautes altitudes
61c            startalt: 95 OK for MY24
62             startalt=70. ! altitude en Km de la transition mid / up
63             delta=30.! Intervalle (km) pour le changement mid /up
64         end if
65
66         !!!!! reglages 35 niveaux FL
67         !fac_mid=3
68         !fac_up=30
69         !startalt=70.
70         !delta=20.
71         !!!! avec dans run.def
72         !!- mode_sponge=3
73         !!- idissip/tetagdiv/tetagrot/tetagtemp = 1/2000/3000/3000
74
75         middle=startalt+delta/2
76         write(*,*) 'Dissipation : '
77         write(*,*) 'Multiplication de la dissipation en altitude :',
78     &          ' fac_mid, fac_up =', fac_mid, fac_up
79         write(*,*) 'Transition mid /up : startalt, delta =',
80     &             startalt, delta , '(km)'
81      endif
82
83c-----------------------------------------------------------------------
84c
85c   calcul des valeurs propres des operateurs par methode iterrative:
86c   -----------------------------------------------------------------
87
88      crot     = -1.
89      cdivu    = -1.
90      cdivh    = -1.
91
92c   calcul de la valeur propre de divgrad:
93c   --------------------------------------
94      idum = 0
95      DO l = 1, llm
96       DO ij = 1, ip1jmp1
97        deltap(ij,l) = 1.
98       ENDDO
99      ENDDO
100
101      idum  = -1
102      zh(1) = RAN1(idum)-.5
103      idum  = 0
104      DO ij = 2, ip1jmp1
105        zh(ij) = RAN1(idum) -.5
106      ENDDO
107
108      CALL filtreg (zh,jjp1,1,2,1,.TRUE.,1)
109
110      CALL minmax(iip1*jjp1,zh,zhmin,zhmax )
111
112      IF ( zhmin .GE. zhmax  )     THEN
113         PRINT*,'  Inidissip  zh min max  ',zhmin,zhmax
114         STOP'probleme generateur alleatoire dans inidissip'
115      ENDIF
116
117      zllm = ABS( zhmax )
118      DO l = 1,50
119         IF(lstardis) THEN
120            CALL divgrad2(1,zh,deltap,niterh,zh)
121         ELSE
122            CALL divgrad (1,zh,niterh,zh)
123         ENDIF
124
125        CALL minmax(iip1*jjp1,zh,zhmin,zhmax )
126
127         zllm  = ABS( zhmax )
128         z1llm = 1./zllm
129         DO ij = 1,ip1jmp1
130            zh(ij) = zh(ij)* z1llm
131         ENDDO
132      ENDDO
133
134      IF(lstardis) THEN
135         cdivh = 1./ zllm
136      ELSE
137         cdivh = zllm ** ( -1./niterh )
138      ENDIF
139
140c   calcul des valeurs propres de gradiv (ii =1) et  nxgrarot(ii=2)
141c   -----------------------------------------------------------------
142      print*,'calcul des valeurs propres'
143
144      DO  20  ii = 1, 2
145c
146         DO ij = 1, ip1jmp1
147           zu(ij)  = RAN1(idum) -.5
148         ENDDO
149         CALL filtreg (zu,jjp1,1,2,1,.TRUE.,1)
150         DO ij = 1, ip1jm
151            zv(ij) = RAN1(idum) -.5
152         ENDDO
153         CALL filtreg (zv,jjm,1,2,1,.FALSE.,1)
154
155         CALL minmax(iip1*jjp1,zu,umin,ullm )
156         CALL minmax(iip1*jjm, zv,vmin,vllm )
157
158         ullm = ABS ( ullm )
159         vllm = ABS ( vllm )
160
161         DO  5  l = 1, 50
162            IF(ii.EQ.1) THEN
163               IF(lstardis) THEN
164                  CALL gradiv2( 1,zu,zv,nitergdiv,zu,zv )
165               ELSE
166                  CALL gradiv ( 1,zu,zv,nitergdiv,zu,zv )
167               ENDIF
168            ELSE
169               IF(lstardis) THEN
170                  CALL nxgraro2( 1,zu,zv,nitergrot,zu,zv )
171               ELSE
172                  CALL nxgrarot( 1,zu,zv,nitergrot,zu,zv )
173               ENDIF
174            ENDIF
175
176            CALL minmax(iip1*jjp1,zu,umin,ullm )
177            CALL minmax(iip1*jjm, zv,vmin,vllm )
178
179            ullm = ABS  ( ullm )
180            vllm = ABS  ( vllm )
181
182            zllm  = MAX( ullm,vllm )
183            z1llm = 1./ zllm
184            DO ij = 1, ip1jmp1
185              zu(ij) = zu(ij)* z1llm
186            ENDDO
187            DO ij = 1, ip1jm
188               zv(ij) = zv(ij)* z1llm
189            ENDDO
190 5       CONTINUE
191
192         IF ( ii.EQ.1 ) THEN
193            IF(lstardis) THEN
194               cdivu  = 1./zllm
195            ELSE
196               cdivu  = zllm **( -1./nitergdiv )
197            ENDIF
198         ELSE
199            IF(lstardis) THEN
200               crot   = 1./ zllm
201            ELSE
202               crot   = zllm **( -1./nitergrot )
203            ENDIF
204         ENDIF
205
206 20   CONTINUE
207
208c   petit test pour les operateurs non star:
209c   ----------------------------------------
210
211c     IF(.NOT.lstardis) THEN
212c        fac_mid    = rad*24./float(jjm)
213c        fac_mid    = fac_mid*fac_mid
214c        PRINT*,'coef u ', fac_mid/cdivu, 1./cdivu
215c        PRINT*,'coef r ', fac_mid/crot , 1./crot
216c        PRINT*,'coef h ', fac_mid/cdivh, 1./cdivh
217c     ENDIF
218
219c-----------------------------------------------------------------------
220c   variation verticale du coefficient de dissipation:
221c   --------------------------------------------------
222
223      DO l=1,llm
224         zvert(l)=1.
225      ENDDO
226
227c
228      DO l = 1, llm
229         zz   = 1. -1./sig_s(l)
230         zvert(l)= fac_mid -( fac_mid-1.)/( 1.+zz*zz )
231
232c ---------------------------------------------------------------
233c Utilisation de la fonction tangente hyperbolique pour augmenter
234c arbitrairement la dissipation et donc la stabilite du modele a
235c partir d'une certaine altitude.
236
237c   Le facteur multiplicatif de basse atmosphere etant deja pris
238c   en compte, il faut diviser le facteur multiplicatif de haute
239c   atmosphere par celui-ci.
240c   ============================================================
241
242         zvert(l)= zvert(l)*(1.0+((fac_up/fac_mid-1)
243     &   *(1-(0.5*(1+tanh(-6./delta*   
244     &   (10.*(-log(sig_s(l)))-middle)))))
245     &   ))
246      ENDDO
247 
248c -----------------------------------------------------------------------------
249
250c
251
252      PRINT*,'Constantes de temps de la diffusion horizontale'
253
254      tetamin =  1.e+6
255
256
257      DO l=1,llm
258        tetaudiv(l)   = zvert(l)/tetagdiv
259        tetaurot(l)   = zvert(l)/tetagrot
260        tetah(l)      = zvert(l)/tetatemp
261
262        IF( tetamin.GT. (1./tetaudiv(l)) ) tetamin = 1./ tetaudiv(l)
263        IF( tetamin.GT. (1./tetaurot(l)) ) tetamin = 1./ tetaurot(l)
264        IF( tetamin.GT. (1./   tetah(l)) ) tetamin = 1./    tetah(l)
265      ENDDO
266
267c     Calcul automatique de idissip
268c     -----------------------------
269c    :::::::::::::::::::::
270c     A Commenter pour garder la valeur de run.def :
271c     idissip = INT( tetamin/( 2.*dtvr*iperiod) ) * iperiod
272c     idissip = MAX(iperiod,idissip)
273c    :::::::::::::::::::::
274      dtdiss  = idissip * dtvr
275 
276      PRINT *,' INIDI tetamin dtvr ',tetamin,dtvr,iperiod
277      PRINT *,' INIDI tetamin idissip ',tetamin,idissip
278      PRINT *,' INIDI idissip dtdiss ',idissip,dtdiss
279
280      PRINT*,'pseudoZ(km)  zvert  dt(tetagdiv) dt(tetagrot) dt(divgrad)'
281      DO l = 1,llm
282         PRINT*,pseudoalt(l),zvert(l),dtdiss*tetaudiv(l),
283     *        dtdiss*tetaurot(l),dtdiss*tetah(l)
284         if ( (dtdiss*tetaudiv(l).gt.1.9).or.
285     &        (dtdiss*tetaurot(l).gt.1.9).or.
286     &        (dtdiss*tetah(l).gt.1.9)) then
287          PRINT *,'STOP : your dissipation is too intense for the '     
288          PRINT *,'dissipation timestep : unstable model !'
289          PRINT *,'in run.def, you must increase tetagdiv,'
290          PRINT *,'(or tetagrot and tetatemp if they are smaller than'
291          PRINT *,'tetagdiv) OR decrease idissip OR increase day_step)'
292          stop
293         end if
294 
295      ENDDO
296c
297      RETURN
298      END
Note: See TracBrowser for help on using the repository browser.