source: trunk/LMDZ.PLUTO.old/libf/dyn3d/nogcm.F_saved_2 @ 3436

Last change on this file since 3436 was 3175, checked in by emillour, 11 months ago

Pluto PCM:
Add the old Pluto LMDZ for reference (required prior step to making
an LMDZ.PLUTO using the same framework as the other physics packages).
TB+EM

File size: 16.8 KB
Line 
1      PROGRAM nogcm
2
3      use comgeomfi_h, only : area_non2,long,lati
4      IMPLICIT NONE
5
6c      ......   Version  du 01/09/15    ..........
7
8c             avec  coordonnees  verticales hybrides
9
10c=======================================================================
11c
12c   Auteur:  F. Forget, T. Bertrand
13c   -------
14c
15c   Objet:
16c   ------
17c
18c   GCM LMD sans dynamique, pour modele saisonnier de surface
19c   
20c=======================================================================
21c
22c-----------------------------------------------------------------------
23c   Declarations:
24c   -------------
25
26#include "dimensions.h"
27#include "paramet.h"
28#include "comconst.h"
29#include "comdissnew.h"
30#include "comvert.h"
31#include "comgeom.h"
32#include "logic.h"
33#include "temps.h"
34#include "control.h"
35#include "ener.h"
36#include "netcdf.inc"
37#include "description.h"
38#include "serre.h"
39#include "tracstoke.h"
40#include "sponge.h"
41#include "advtrac.h"
42#include "callkeys.h"
43#include "tracer.h"
44#include "dimphys.h"
45#include "surfdat.h"
46
47      INTEGER*4  iday ! jour julien
48      REAL       time ! Heure de la journee en fraction d''1 jour
49      REAL zdtvr
50
51
52c   variables dynamiques
53      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
54      real, dimension(ip1jmp1,llm) :: teta   ! temperature potentielle
55      REAL q(ip1jmp1,llm,nqmx)               ! champs advectes
56      REAL ps(ip1jmp1)                       ! pression  au sol
57      REAL kpd(ip1jmp1)                       ! TB15 = exp (-z/H)
58      REAL p (ip1jmp1,llmp1  )               ! pression aux interfac.des couches
59      REAL pks(ip1jmp1)                      ! exner au  sol
60      REAL pk(ip1jmp1,llm)                   ! exner au milieu des couches
61      REAL pkf(ip1jmp1,llm)                  ! exner filt.au milieu des couches
62      REAL masse(ip1jmp1,llm)                ! masse d''air
63      REAL phis(ip1jmp1)                     ! geopotentiel au sol
64      REAL phi(ip1jmp1,llm)                  ! geopotentiel
65      REAL w(ip1jmp1,llm)                    ! vitesse verticale
66
67c   tendances dynamiques
68      REAL dv(ip1jm,llm),du(ip1jmp1,llm)
69      REAL dteta(ip1jmp1,llm),dq(ip1jmp1,llm,nqmx)
70
71c   tendances physiques
72      REAL dvfi(ip1jm,llm),dufi(ip1jmp1,llm)
73      REAL dhfi(ip1jmp1,llm),dqfi(ip1jmp1,llm,nqmx),dpfi(ip1jmp1)
74
75c   variables pour le fichier histoire
76      REAL dtav      ! intervalle de temps elementaire
77
78      INTEGER itau,itaufinp1
79
80      EXTERNAL traceur
81      EXTERNAL iniconst
82      EXTERNAL SCOPY
83      EXTERNAL inigeom
84      EXTERNAL exner_hyb,addit
85      EXTERNAL defrun_new, test_period
86      REAL time_0
87
88      LOGICAL lafin
89      INTEGER ij
90
91      REAL rdayvrai,rdaym_ini,rday_ecri
92      REAL beta(ip1jmp1,llm)
93
94      character*20 modname
95      character*80 abort_message
96
97      INTEGER nq, numvanle
98
99      REAL psmean                    ! pression moyenne
100      REAL p0                        ! pression de reference
101      REAL p00d                        ! globalaverage(kpd)
102      REAL qmean_ch4                    ! mass mean mixing ratio vap ch4
103      REAL qmean_co                    ! mass mean mixing ratio vap co
104      REAL pqch4(ip1jmp1)           ! average methane mass index : ps*qch4
105      REAL pqco(ip1jmp1)           ! average methane mass index : ps*q_co
106      REAL oldps(ip1jmp1)           ! saving old pressure ps to calculate qch4
107
108! flag to set/remove calls to groupeun
109      real globaverage2d   
110      real globaverage2d_non2 
111      logical firstphys
112      data firstphys/.true./
113      save firstphys
114c-----------------------------------------------------------------------
115c   Initialisations:
116c   ----------------
117
118      modname = 'gcm'
119      descript = 'Run GCM LMDZ'
120      lafin    = .FALSE.
121     
122c-----------------------------------------------------------------------
123c  Initialize tracers using iniadvtrac (Ehouarn, oct 2008)
124      CALL iniadvtrac(nq,numvanle)
125
126      CALL dynetat0("start.nc",nqmx,vcov,ucov,
127     .              teta,q,masse,ps,phis, time_0)
128      CALL defrun_new( 99, .TRUE. )
129      write(*,*) 'TB15: test0 r, cpp=',r,cpp
130
131c  on recalcule eventuellement le pas de temps
132
133      IF(MOD(day_step,iperiod).NE.0)
134     * STOP'Il faut choisir un nb de pas par jour multiple de iperiod'
135
136c      IF(MOD(day_step,iphysiq).NE.0)
137c     * STOP'Il faut choisir un nb de pas par jour multiple de iphysiq'
138
139      zdtvr    = daysec/FLOAT(day_step)
140
141        IF(dtvr.NE.zdtvr) THEN
142         PRINT*,'WARNING!!! changement de pas de temps',dtvr,'>',zdtvr
143        ENDIF
144
145c  nombre d etats dans les fichiers demarrage et histoire
146
147      dtvr = zdtvr
148      CALL iniconst
149      CALL inigeom
150c      CALL inifilr
151
152c   ......    P.Le Van    ( modif  le 29/04/97 )   ......... 
153
154c      CALL inidissip ( lstardis, nitergdiv, nitergrot, niterh   ,
155c     *                tetagdiv, tetagrot , tetatemp              )
156
157      CALL pression ( ip1jmp1, ap, bp, ps, p       )
158      call dump2d(iip1,jjp1,ps,'PRESSION SURFACE')
159      CALL exner_hyb( ip1jmp1, ps, p,beta, pks, pk, pkf )
160
161c
162c  numero de stockage pour les fichiers de redemarrage:
163
164c-----------------------------------------------------------------------
165c   temps de depart et de fin:
166c   --------------------------
167
168      itau = 0
169      iday = day_ini+itau/day_step
170      time = FLOAT(itau-(iday-day_ini)*day_step)/day_step+time_0
171
172
173         IF(time.GT.1.) THEN
174          time = time-1.
175          iday = iday+1
176         ENDIF
177      itaufin   = nday*day_step
178      itaufinp1 = itaufin +1
179
180      day_end = day_ini + nday
181      write(*,*) "TB16:",day_ini,nday,day_end
182      PRINT 300, itau,itaufin,day_ini,day_end
183 300  FORMAT('1'/,15x,'run du pas',i7,2x,'au pas',i7,2x, 
184     . 'c''est a dire du jour',i7,3x,'au jour',i7//)
185
186      CALL dynredem0("restart.nc",day_end,anne_ini,phis,nqmx)
187       
188      ecripar = .TRUE.
189
190      dtav = iperiod*dtvr/daysec
191
192
193c   Quelques initialisations pour les traceurs
194      call initial0(ijp1llm*nqmx,dq)
195c     istdyn=day_step/4     ! stockage toutes les 6h=1jour/4
196c     istphy=istdyn/iphysiq
197
198c      CALL geopot  ( ip1jmp1, teta  , pk , pks,  phis  , phi   )
199
200c-----------------------------------------------------------------------
201c   Debut de l integration temporelle:
202c   ----------------------------------
203
204c     kpd=exp(-z/H)  Needed to define a reference pressure :
205c     P0=pmean/globalaverage(kpd) 
206c     thus P(i) = P0*exp(-z(i)/H) = P0*kpd(i)
207c     It is checked that globalaverage2d(Pi)=pmean
208      DO ij=1,ip1jmp1
209             kpd(ij) = exp(-phis(ij)/(r*38.))
210      ENDDO
211      p00d=globaverage2d(kpd) ! mean pres at ref level
212
213c      tau_n2 = 1. ! constante de rappel for pressure n2 (s)
214c      tau_ch4 = 1.E7 ! constante de rappel for mix ratio qch4 (s)
215c      tau_co = 1. !E5 ! constante de rappel for mix ratio qco (s)
216
217      dt      =  dtvr
218      dtphys  = iphysiq * dtvr
219      DO itau = 1,itaufin
220
221        apphys = ( MOD(itau+1,iphysiq ).EQ.0.AND. physic)
222c-----------------------------------------------------------------------
223c   calcul des tendances physiques:
224c -------------------------------
225        IF( itau+1.EQ.itaufin) lafin = .TRUE.
226c
227        IF( apphys )  THEN
228           rdaym_ini  = (itau) * dtvr / daysec
229           rdayvrai   = rdaym_ini  + day_ini
230           IF ( ecritphy.LT.1. )  THEN
231             rday_ecri = rdaym_ini
232           ELSE
233             rday_ecri = INT(rdaym_ini)+INT(day_ini)
234           ENDIF
235c           write(20,*) 'TB15 : ps1 nogcm= ',globaverage2d(ps)  ! mean pressure
236
237           CALL calfis( nqmx, lafin ,rdayvrai,rday_ecri,time  ,
238     $                 ucov,vcov,teta,q,masse,ps,p,pk,phis,phi ,
239     $     du,dv,dteta,dq,w,dufi,dvfi,dhfi,dqfi,dpfi,tracer)
240c           write(21,*) 'TB15 : ps2 nogcm= ',globaverage2d(ps)  ! mean pressure
241
242c          saving pressure pplev :
243           DO ij=1,ip1jmp1
244               oldps(ij)=ps(ij)             
245           ENDDO
246
247c          increment q_ch4 with physical tendancy
248           if (methane) then
249             DO ij=1,ip1jmp1
250                 q(ij,1,igcm_ch4_gas)=q(ij,1,igcm_ch4_gas)+
251     &                    dqfi(ij,1,igcm_ch4_gas)*dtphys
252             ENDDO
253c             write(31,*) 'TB15 : qch4 t1 = ',
254c     &                     globaverage2d(q(:,1,igcm_ch4_gas)*ps(:)/g)
255           endif
256
257c          increment q_co with physical tendancy
258           if (carbox) then
259             DO ij=1,ip1jmp1
260                 q(ij,1,igcm_co_gas)=q(ij,1,igcm_co_gas)+
261     &                    dqfi(ij,1,igcm_co_gas)*dtphys
262             ENDDO
263!             write(41,*) 'TB15 : qco t1 = ',
264!     &                     globaverage2d(q(:,1,igcm_co_gas)*ps(:)/g)
265           ENDIF
266
267c          update pressure
268           DO ij=1,ip1jmp1
269             ps(ij) = ps(ij) + dpfi(ij)*dtphys
270           ENDDO
271
272           psmean= globaverage2d(ps)  ! mean pressure
273           p0=psmean/p00d
274           DO ij=1,ip1jmp1
275             ! Rappel newtonien vers psmean
276             ps(ij)=ps(ij) +(p0*kpd(ij)
277     &                  -ps(ij))*(1-exp(-dtphys/tau_n2))
278           ENDDO
279
280           write(72,*) 'TB15 : ps redistributed = ',psmean  ! mean pressure
281           write(72,*) ' '
282
283c          TB15 : test pressure negative
284           DO ij=1,ip1jmp1
285             IF (ps(ij).le.0.) then
286                 write(*,*) 'Negative pressure :'
287                 write(*,*) 'ps = ',ps(ij),' ig = ',ij
288                 write(*,*) 'pmean = ',p0*kpd(ij)
289                 write(*,*) 'tau_n2 = ',tau_n2
290                 STOP
291             ENDIF
292           ENDDO
293
294           if (methane) then
295             ! Simulate redistribution by dynamics for qch4
296             DO ij=1,ip1jmp1
297c              update mmr q for new pressure
298c              (both q and dqfi were calculated with old pressure in physiq)
299               q(ij,1,igcm_ch4_gas)=q(ij,1,igcm_ch4_gas)*oldps(ij)/
300     &                                                           ps(ij)
301               ! average methane mass index : ps * qch4 => 'pressure of ch4'
302               pqch4(ij)= ps(ij) * q(ij,1,igcm_ch4_gas)
303             end do
304c             write(32,*) 'TB15 : qch4 t2 = ',
305c     &                     globaverage2d(q(:,1,igcm_ch4_gas)*ps(:)/g)
306             ! weighted averaged CH4 mass mixing ratio:
307             qmean_ch4= globaverage2d(pqch4) / globaverage2d(ps)
308             !qmean_ch4=globaverage2d_non2(pqch4)/globaverage2d_non2(ps)
309             DO ij=1,ip1jmp1
310               !write(*,*) area_non2(ij),long(ij)*57.3,lati(ij)*57.3
311               ! Rappel newtonien vers qmean
312               !IF (area_non2(ij).gt.0.) THEN
313                  q(ij,1,igcm_ch4_gas)=q(ij,1,igcm_ch4_gas) +(qmean_ch4
314     &                  -q(ij,1,igcm_ch4_gas))*(1.-exp(-dtphys/tau_ch4))
315               !ENDIF
316             ENDDO
317c             write(33,*) 'TB15 : qch4 t3 = ',
318c     &                     globaverage2d(q(:,1,igcm_ch4_gas)*ps(:)/g)
319           endif
320
321           if (carbox) then
322             ! Simulate redistribution by dynamics for q_co
323             DO ij=1,ip1jmp1
324c              update mmr q for new pressure
325c              (both q and dqfi were calculated with old pressure in physiq)
326               q(ij,1,igcm_co_gas)=q(ij,1,igcm_co_gas)*oldps(ij)/
327     &                                                           ps(ij)
328               ! average methane mass index : ps * q_co
329               pqco(ij)= ps(ij) * q(ij,1,igcm_co_gas)
330             end do
331!             write(42,*) 'TB15 : qco t2 = ',
332!     &                     globaverage2d(q(:,1,igcm_co_gas)*ps(:)/g)
333             ! weighted averaged CO mass mixing ratio:
334             qmean_co= globaverage2d(pqco) / globaverage2d(ps)
335             DO ij=1,ip1jmp1
336               ! Rappel newtonien vers qmean
337               q(ij,1,igcm_co_gas)=q(ij,1,igcm_co_gas) +(qmean_co
338     &                  -q(ij,1,igcm_co_gas))*(1.-exp(-dtphys/tau_co))
339             ENDDO
340!             write(43,*) 'TB15 : qco t3 = ',
341!     &                     globaverage2d(q(:,1,igcm_co_gas)*ps(:)/g)
342           endif
343
344ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
345
346
347           CALL pression ( ip1jmp1, ap, bp, ps, p                  )
348           CALL massdair (     p  , masse         )
349           CALL exner_hyb( ip1jmp1, ps, p,beta, pks, pk, pkf )
350
351          if(firstphys) then
352
353c            Option Special "nogcm"
354c            ---------------
355             corrk      = .false.
356             calldifv = .false.
357             calladj  = .false.
358             callconduct=.false.
359             IF (paleo) then
360              day_end=int(day_ini+paleoyears*365.25/6.3872)+1
361              CALL gr_fi_dyn(1,ngridmx,iip1,jjp1,phisfi,phis)
362              ! appel a dynredem0 apes passage dans physiq pour
363              ! recuperer phisfi (=>phis) et paleoyears)
364              CALL dynredem0("restart.nc",day_end,anne_ini,phis,nqmx)
365             ENDIF
366
367             write(*,*) '**********************************************'
368             write(*,*) 'WARNING: For nogcm, these options are forced:'
369             write(*,*) '**********************************************'
370             write(*,*) 'Option corrk = ', corrk
371             write(*,*) 'Option  calldifv = ',  calldifv
372             write(*,*) 'Option  calladj = ', calladj
373             write(*,*) 'Option  callconduct = ', callconduct
374             write(*,*) 'tau N2 - CH4 - CO = ', tau_n2,tau_ch4,tau_co
375             write(*,*) '**********************************************'
376             firstphys=.false.
377          end if
378        ENDIF
379
380c   ********************************************************************
381c   .... fin de l'integration dynamique  et physique pour le pas itau ..
382c   ********************************************************************
383
384c       preparation du pas d'integration suivant  ......
385
386        iday= day_ini+itau/day_step
387        time= FLOAT(itau+1-(iday-day_ini)*day_step)/day_step+time_0
388        IF(time.GT.1.) THEN
389             time = time-1.
390             iday = iday+1
391        ENDIF
392       
393c-----------------------------------------------------------------------
394
395        IF(itau.EQ.itaufin) THEN
396           PRINT *,' Appel test_period avant redem ', itau
397
398c           TBch4 : coupe test period car nous embete pour des pouilleme
399c           sur le ch4_gas
400           CALL test_period ( ucov,vcov,teta,q,p,phis )
401           CALL dynredem1("restart.nc",0.0,
402     .                     vcov,ucov,teta,q,nqmx,masse,ps)
403              CLOSE(99)
404        ENDIF
405
406      END DO   ! fin de la boucle temporelle
407      abort_message = 'Simulation finished'
408      call abort_gcm(modname,abort_message,0)
409
410      STOP
411      END
412
413!*********************************************************************************
414      FUNCTION globaverage2d(var)
415      IMPLICIT NONE
416#include "dimensions.h"
417#include "paramet.h"
418#include "comgeom2.h"
419
420       REAL var(iip1,jjp1), globaverage2d
421       integer i,j
422       REAL airetot
423       save airetot
424       logical firstcall
425       data firstcall/.true./
426       save firstcall
427
428       if (firstcall) then
429         firstcall=.false.
430c         write(30,*) 'TB15 : aire = ',aire
431         airetot =0.
432         DO j=2,jjp1-1      ! lat
433           DO i = 1, iim    ! lon
434             airetot = airetot + aire(i,j)
435           END DO
436         END DO
437         airetot=airetot + aire(1,1)+aire(1,jjp1)
438c         write(*,*) 'TB15 : nogcm totarea= ',airetot
439       end if
440
441       globaverage2d = 0.
442       DO j=2,jjp1-1
443         DO i = 1, iim
444           globaverage2d = globaverage2d + var(i,j)*aire(i,j)
445         END DO
446       END DO
447       globaverage2d = globaverage2d + var(1,1)*aire(1,1)
448       globaverage2d = globaverage2d + var(1,jjp1)*aire(1,jjp1)
449       globaverage2d = globaverage2d/airetot
450      return
451      end
452!*********************************************************************************
453      FUNCTION globaverage2d_non2(var)
454      use comgeomfi_h, only : area_non2
455      IMPLICIT NONE
456#include "dimensions.h"
457#include "dimphys.h"
458#include "paramet.h"
459!#include "comgeom2.h"
460!#include "comgeomfi.h"
461
462       REAL var(iip1,jjp1), globaverage2d_non2
463       integer i,j
464       REAL airetot_non2
465       save airetot_non2
466       REAL aire_non2(iip1,jjp1)
467       save aire_non2
468       logical firstcall
469       data firstcall/.true./
470       save firstcall
471       
472       ! get aire_non2 : aire SP
473       ! calculate sum : airetot_non2
474       if (firstcall) then
475         firstcall=.false.
476         CALL gr_fi_dyn(1,ngridmx,iip1,jjp1,area_non2,aire_non2)
477         airetot_non2 =0.
478         DO j=2,jjp1-1      ! lat
479           DO i = 1, iim    ! lon
480             airetot_non2 = airetot_non2 + aire_non2(i,j)
481             write(*,*) aire_non2(j,i)
482           END DO
483         END DO
484         airetot_non2=airetot_non2 + aire_non2(1,1)+aire_non2(1,jjp1)
485       end if
486
487       ! Global average:
488       globaverage2d_non2 = 0.
489       DO j=2,jjp1-1
490         DO i = 1, iim
491           globaverage2d_non2 = globaverage2d_non2 +
492     &                               var(i,j)*aire_non2(i,j)
493         END DO
494       END DO
495       globaverage2d_non2 = globaverage2d_non2 + var(1,1)*aire_non2(1,1)
496       globaverage2d_non2 = globaverage2d_non2 +
497     &                               var(1,jjp1)*aire_non2(1,jjp1)
498       globaverage2d_non2 = globaverage2d_non2/airetot_non2
499      return
500      end 
Note: See TracBrowser for help on using the repository browser.