source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/start2archive.F @ 253

Last change on this file since 253 was 227, checked in by milmd, 10 years ago

Last LMDZ version (1315) with OpenMP directives and other stuff

File size: 18.2 KB
Line 
1c=======================================================================
2      PROGRAM start2archive
3c=======================================================================
4c
5c
6c   Date:    01/1997
7c   ----
8c
9c
10c   Objet:   Passage des  fichiers netcdf d'etat initial "start" et
11c   -----    "startfi" a un fichier netcdf unique "start_archive"
12c
13c  "start_archive" est une banque d'etats initiaux:
14c  On peut stocker plusieurs etats initiaux dans un meme fichier "start_archive"
15c    (Veiller dans ce cas avoir un day_ini different pour chacun des start)
16c 
17c
18c
19c=======================================================================
20
21      use infotrac, only: iniadvtrac, nqtot, tname
22      USE comsoil_h
23      USE comgeomfi_h, ONLY: lati, long, area
24!      use control_mod
25      use comgeomphy, only: initcomgeomphy
26      use slab_ice_h, only: noceanmx
27! to use  'getin'
28      USE ioipsl_getincom
29      USE planete_mod
30
31      implicit none
32
33#include "dimensions.h"
34      integer, parameter :: ngridmx = (2+(jjm-1)*iim - 1/jjm) 
35#include "paramet.h"
36#include "comconst.h"
37#include "comdissip.h"
38#include "comvert.h"
39#include "comgeom.h"
40#include "logic.h"
41#include "temps.h"
42!#include "control.h"
43#include "ener.h"
44
45!#include "dimphys.h"
46!#include "planete.h"
47!#include"advtrac.h"
48#include "netcdf.inc"
49#include "callkeys.h"
50c-----------------------------------------------------------------------
51c   Declarations
52c-----------------------------------------------------------------------
53
54c variables dynamiques du GCM
55c -----------------------------
56      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
57      REAL teta(ip1jmp1,llm)                    ! temperature potentielle
58      REAL,ALLOCATABLE :: q(:,:,:)   ! champs advectes
59      REAL pks(ip1jmp1)                      ! exner (f pour filtre)
60      REAL pk(ip1jmp1,llm)
61      REAL pkf(ip1jmp1,llm)
62      REAL beta(iip1,jjp1,llm)
63      REAL phis(ip1jmp1)                     ! geopotentiel au sol
64      REAL masse(ip1jmp1,llm)                ! masse de l'atmosphere
65      REAL ps(ip1jmp1)                       ! pression au sol
66      REAL p3d(iip1, jjp1, llm+1)            ! pression aux interfaces
67     
68c Variable Physiques (grille physique)
69c ------------------------------------
70      REAL tsurf(ngridmx)       ! Surface temperature
71      REAL tsoil(ngridmx,nsoilmx) ! Soil temperature
72      REAL co2ice(ngridmx)      ! CO2 ice layer
73      REAL q2(ngridmx,llm+1)
74      REAL,ALLOCATABLE :: qsurf(:,:)
75      REAL emis(ngridmx)
76      INTEGER start,length
77      PARAMETER (length = 100)
78      REAL tab_cntrl_fi(length) ! tableau des parametres de startfi
79      REAL tab_cntrl_dyn(length) ! tableau des parametres de start
80      INTEGER*4 day_ini_fi
81
82!     added by FF for cloud fraction setup
83      REAL hice(ngridmx)
84      REAL cloudfrac(ngridmx,llm),totalcloudfrac(ngridmx)
85
86!     added by BC for slab ocean
87      REAL rnat(ngridmx),pctsrf_sic(ngridmx),sea_ice(ngridmx)
88      REAL tslab(ngridmx,noceanmx),tsea_ice(ngridmx)
89
90
91c Variable naturelle / grille scalaire
92c ------------------------------------
93      REAL T(ip1jmp1,llm),us(ip1jmp1,llm),vs(ip1jmp1,llm)
94      REAL tsurfS(ip1jmp1)
95      REAL tsoilS(ip1jmp1,nsoilmx)
96      REAL ithS(ip1jmp1,nsoilmx) ! Soil Thermal Inertia
97      REAL co2iceS(ip1jmp1)
98      REAL q2S(ip1jmp1,llm+1)
99      REAL,ALLOCATABLE :: qsurfS(:,:)
100      REAL emisS(ip1jmp1)
101
102!     added by FF for cloud fraction setup
103      REAL hiceS(ip1jmp1)
104      REAL cloudfracS(ip1jmp1,llm),totalcloudfracS(ip1jmp1)
105
106!     added by BC for slab ocean
107      REAL rnatS(ip1jmp1),pctsrf_sicS(ip1jmp1),sea_iceS(ip1jmp1)
108      REAL tslabS(ip1jmp1,noceanmx),tsea_iceS(ip1jmp1)
109
110
111c Variables intermediaires : vent naturel, mais pas coord scalaire
112c----------------------------------------------------------------
113      REAL vn(ip1jm,llm),un(ip1jmp1,llm)
114
115c Autres  variables
116c -----------------
117      LOGICAL startdrs
118      INTEGER Lmodif
119
120      REAL ptotal, co2icetotal
121      REAL timedyn,timefi !fraction du jour dans start, startfi
122      REAL date
123
124      CHARACTER*2 str2
125      CHARACTER*80 fichier 
126      data  fichier /'startfi'/
127
128      INTEGER ij, l,i,j,isoil,iq
129      character*80      fichnom
130      integer :: ierr,ntime
131      integer :: nq,numvanle
132      character(len=30) :: txt ! to store some text
133
134c Netcdf
135c-------
136      integer varid,dimid,timelen 
137      INTEGER nid,nid1
138
139c-----------------------------------------------------------------------
140c   Initialisations 
141c-----------------------------------------------------------------------
142
143      CALL defrun_new(99, .TRUE. )
144      grireg   = .TRUE.
145
146! initialize "serial/parallel" related stuff
147      CALL init_phys_lmdz(iim,jjp1,llm,1,(/(jjm-1)*iim+2/))
148      call initcomgeomphy
149
150      ! ALLOCATE ARRAYS IN comgeomfi_h (usually done in inifis)
151      ! this must be here for start2archive to work
152      IF (.not. ALLOCATED(lati)) ALLOCATE(lati(ngridmx))
153      IF (.not. ALLOCATED(long)) ALLOCATE(long(ngridmx))
154      IF (.not. ALLOCATED(area)) ALLOCATE(area(ngridmx))
155
156c=======================================================================
157c Lecture des donnees
158c=======================================================================
159! Load tracer number and names:
160      call iniadvtrac(nqtot,numvanle)
161
162! allocate arrays:
163      allocate(q(ip1jmp1,llm,nqtot))
164      allocate(qsurf(ngridmx,nqtot))
165      allocate(qsurfS(ip1jmp1,nqtot))
166! other array allocations:
167      call ini_comsoil_h(ngridmx)
168
169      fichnom = 'start.nc'
170      CALL dynetat0(fichnom,nqtot,vcov,ucov,teta,q,masse,
171     .       ps,phis,timedyn)
172
173! load 'controle' array from dynamics start file
174
175       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
176       IF (ierr.NE.NF_NOERR) THEN
177         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
178        CALL ABORT
179       ENDIF
180                                               
181      ierr = NF_INQ_VARID (nid1, "controle", varid)
182      IF (ierr .NE. NF_NOERR) THEN
183       PRINT*, "start2archive: Le champ <controle> est absent"
184       CALL abort
185      ENDIF
186#ifdef NC_DOUBLE
187       ierr = NF_GET_VAR_DOUBLE(nid1, varid, tab_cntrl_dyn)
188#else
189      ierr = NF_GET_VAR_REAL(nid1, varid, tab_cntrl_dyn)
190#endif
191       IF (ierr .NE. NF_NOERR) THEN
192          PRINT*, "start2archive: Lecture echoue pour <controle>"
193          CALL abort
194       ENDIF
195
196      ierr = NF_CLOSE(nid1)
197     
198
199      fichnom = 'startfi.nc'
200      Lmodif=0
201
202
203      CALL phyetat0 (ngridmx,llm,fichnom,0,Lmodif,nsoilmx,nqtot,
204     .      day_ini_fi,timefi,
205     .      tsurf,tsoil,emis,q2,qsurf,
206!       change FF 05/2011
207     .       cloudfrac,totalcloudfrac,hice,
208!       change BC 05/2014
209     .       rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
210
211
212
213
214! load 'controle' array from physics start file
215
216       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
217       IF (ierr.NE.NF_NOERR) THEN
218         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
219        CALL ABORT
220       ENDIF
221                                               
222      ierr = NF_INQ_VARID (nid1, "controle", varid)
223      IF (ierr .NE. NF_NOERR) THEN
224       PRINT*, "start2archive: Le champ <controle> est absent"
225       CALL abort
226      ENDIF
227#ifdef NC_DOUBLE
228       ierr = NF_GET_VAR_DOUBLE(nid1, varid, tab_cntrl_fi)
229#else
230      ierr = NF_GET_VAR_REAL(nid1, varid, tab_cntrl_fi)
231#endif
232       IF (ierr .NE. NF_NOERR) THEN
233          PRINT*, "start2archive: Lecture echoue pour <controle>"
234          CALL abort
235       ENDIF
236
237      ierr = NF_CLOSE(nid1)
238
239
240c-----------------------------------------------------------------------
241c Controle de la synchro
242c-----------------------------------------------------------------------
243!mars a voir      if ((day_ini_fi.ne.day_ini).or.(abs(timefi-timedyn).gt.1.e-10))
244      if ((day_ini_fi.ne.day_ini)) 
245     &  stop ' Probleme de Synchro entre start et startfi !!!'
246
247
248c *****************************************************************
249c    Option : Reinitialisation des dates dans la premieres annees :
250       do while (day_ini.ge.year_day)
251          day_ini=day_ini-year_day
252       enddo
253c *****************************************************************
254
255c-----------------------------------------------------------------------
256c   Initialisations 
257c-----------------------------------------------------------------------
258
259      CALL defrun_new(99, .FALSE. )
260      call iniconst
261      call inigeom
262      call inifilr
263      CALL pression(ip1jmp1, ap, bp, ps, p3d)
264      call exner_hyb(ip1jmp1, ps, p3d, beta, pks, pk, pkf)
265
266c=======================================================================
267c Transformation EN VARIABLE NATURELLE / GRILLE SCALAIRE si necessaire
268c=======================================================================
269c  Les variables modeles dependent de la resolution. Il faut donc
270c  eliminer les facteurs responsables de cette dependance
271c  (pour utiliser newstart)
272c=======================================================================
273
274c-----------------------------------------------------------------------
275c Vent   (depend de la resolution horizontale) 
276c-----------------------------------------------------------------------
277c
278c ucov --> un  et  vcov --> vn
279c un --> us  et   vn --> vs
280c
281c-----------------------------------------------------------------------
282
283      call covnat(llm,ucov, vcov, un, vn) 
284      call wind_scal(un,vn,us,vs) 
285
286c-----------------------------------------------------------------------
287c Temperature  (depend de la resolution verticale => de "sigma.def")
288c-----------------------------------------------------------------------
289c
290c h --> T
291c
292c-----------------------------------------------------------------------
293
294      DO l=1,llm
295         DO ij=1,ip1jmp1
296            T(ij,l)=teta(ij,l)*pk(ij,l)/cpp !mars deduit de l'equation dans newstart
297         ENDDO
298      ENDDO
299
300c-----------------------------------------------------------------------
301c Variable physique 
302c-----------------------------------------------------------------------
303c
304c tsurf --> tsurfS
305c co2ice --> co2iceS
306c tsoil --> tsoilS
307c emis --> emisS
308c q2 --> q2S
309c qsurf --> qsurfS
310c
311c-----------------------------------------------------------------------
312
313      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tsurf,tsurfS)
314!      call gr_fi_dyn(1,ngridmx,iip1,jjp1,co2ice,co2iceS)
315      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,tsoil,tsoilS)
316      ! Note: thermal inertia "inertiedat" is in comsoil.h
317      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,inertiedat,ithS)
318      call gr_fi_dyn(1,ngridmx,iip1,jjp1,emis,emisS)
319      call gr_fi_dyn(llm+1,ngridmx,iip1,jjp1,q2,q2S)
320      call gr_fi_dyn(nqtot,ngridmx,iip1,jjp1,qsurf,qsurfS)
321      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,cloudfrac,cloudfracS)
322      call gr_fi_dyn(1,ngridmx,iip1,jjp1,hice,hiceS)
323      call gr_fi_dyn(1,ngridmx,iip1,jjp1,totalcloudfrac,totalcloudfracS)
324
325      call gr_fi_dyn(1,ngridmx,iip1,jjp1,rnat,rnatS)
326      call gr_fi_dyn(1,ngridmx,iip1,jjp1,pctsrf_sic,pctsrf_sicS)
327      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tsea_ice,tsea_iceS)
328      call gr_fi_dyn(1,ngridmx,iip1,jjp1,sea_ice,sea_iceS)
329      call gr_fi_dyn(noceanmx,ngridmx,iip1,jjp1,tslab,tslabS)
330
331c=======================================================================
332c Info pour controler
333c=======================================================================
334
335      ptotal =  0.
336      co2icetotal = 0.
337      DO j=1,jjp1
338         DO i=1,iim
339           ptotal=ptotal+aire(i+(iim+1)*(j-1))*ps(i+(iim+1)*(j-1))/g
340!           co2icetotal = co2icetotal +
341!     &            co2iceS(i+(iim+1)*(j-1))*aire(i+(iim+1)*(j-1))
342         ENDDO
343      ENDDO
344      write(*,*)'Ancienne grille : masse de l''atm :',ptotal
345!      write(*,*)'Ancienne grille : masse de la glace CO2 :',co2icetotal
346
347c-----------------------------------------------------------------------
348c Passage de "ptotal" et "co2icetotal" par tab_cntrl_fi
349c-----------------------------------------------------------------------
350
351      tab_cntrl_fi(49) = ptotal
352      tab_cntrl_fi(50) = co2icetotal
353
354c=======================================================================
355c Ecriture dans le fichier  "start_archive"
356c=======================================================================
357
358c-----------------------------------------------------------------------
359c Ouverture de "start_archive" 
360c-----------------------------------------------------------------------
361
362      ierr = NF_OPEN ('start_archive.nc', NF_WRITE,nid)
363 
364c-----------------------------------------------------------------------
365c  si "start_archive" n'existe pas:
366c    1_ ouverture
367c    2_ creation de l'entete dynamique ("ini_archive")
368c-----------------------------------------------------------------------
369c ini_archive:
370c On met dans l'entete le tab_cntrl dynamique (1 a 16)
371c  On y ajoute les valeurs du tab_cntrl_fi (a partir de 51)
372c  En plus les deux valeurs ptotal et co2icetotal (99 et 100)
373c-----------------------------------------------------------------------
374
375      if (ierr.ne.NF_NOERR) then
376         write(*,*)'OK, Could not open file "start_archive.nc"'
377         write(*,*)'So let s create a new "start_archive"'
378         ierr = NF_CREATE('start_archive.nc', NF_CLOBBER, nid)
379         call ini_archive(nid,day_ini,phis,ithS,tab_cntrl_fi,
380     &                                          tab_cntrl_dyn)
381      endif
382
383c-----------------------------------------------------------------------
384c Ecriture de la coordonnee temps (date en jours)
385c-----------------------------------------------------------------------
386
387      date = day_ini
388      ierr= NF_INQ_VARID(nid,"Time",varid)
389      ierr= NF_INQ_DIMID(nid,"Time",dimid)
390      ierr= NF_INQ_DIMLEN(nid,dimid,timelen)
391      ntime=timelen+1
392
393      write(*,*) "******************"
394      write(*,*) "ntime",ntime
395      write(*,*) "******************"
396#ifdef NC_DOUBLE
397      ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
398#else
399      ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
400#endif
401      if (ierr.ne.NF_NOERR) then
402         write(*,*) "time matter ",NF_STRERROR(ierr)
403         stop
404      endif
405
406c-----------------------------------------------------------------------
407c Ecriture des champs  (co2ice,emis,ps,Tsurf,T,u,v,q2,q,qsurf)
408c-----------------------------------------------------------------------
409c ATTENTION: q2 a une couche de plus!!!!
410c    Pour creer un fichier netcdf lisible par grads,
411c    On passe donc une des couches de q2 a part
412c    comme une variable 2D (la couche au sol: "q2surf")
413c    Les lmm autres couches sont nommees "q2atm" (3D)
414c-----------------------------------------------------------------------
415
416!      call write_archive(nid,ntime,'co2ice','couche de glace co2',
417!     &  'kg/m2',2,co2iceS)
418      call write_archive(nid,ntime,'emis','grd emis',' ',2,emisS)
419      call write_archive(nid,ntime,'ps','Psurf','Pa',2,ps)
420      call write_archive(nid,ntime,'tsurf','surf T','K',2,tsurfS)
421      call write_archive(nid,ntime,'temp','temperature','K',3,t)
422      call write_archive(nid,ntime,'u','Vent zonal','m.s-1',3,us)
423      call write_archive(nid,ntime,'v','Vent merid','m.s-1',3,vs)
424      call write_archive(nid,ntime,'q2surf','wind variance','m2.s-2',2,
425     .              q2S)
426      call write_archive(nid,ntime,'q2atm','wind variance','m2.s-2',3,
427     .              q2S(1,2))
428
429c-----------------------------------------------------------------------
430c Ecriture du champs  q  ( q[1,nqtot] )
431c-----------------------------------------------------------------------
432      do iq=1,nqtot
433        call write_archive(nid,ntime,tname(iq),'tracer','kg/kg',
434     &         3,q(1,1,iq))
435      end do
436c-----------------------------------------------------------------------
437c Ecriture du champs  qsurf  ( qsurf[1,nqtot] )
438c-----------------------------------------------------------------------
439      do iq=1,nqtot
440        txt=trim(tname(iq))//"_surf"
441        call write_archive(nid,ntime,txt,'Tracer on surface',
442     &  'kg.m-2',2,qsurfS(1,iq))
443      enddo
444
445
446c-----------------------------------------------------------------------
447c Ecriture du champs  tsoil  ( Tg[1,10] )
448c-----------------------------------------------------------------------
449c "tsoil" Temperature au sol definie dans 10 couches dans le sol
450c   Les 10 couches sont lues comme 10 champs
451c  nommees Tg[1,10]
452
453c      do isoil=1,nsoilmx
454c       write(str2,'(i2.2)') isoil
455c       call write_archive(nid,ntime,'Tg'//str2,'Ground Temperature ',
456c     .   'K',2,tsoilS(1,isoil))
457c      enddo
458
459! Write soil temperatures tsoil
460      call write_archive(nid,ntime,'tsoil','Soil temperature',
461     &     'K',-3,tsoilS)
462
463! Write soil thermal inertia
464      call write_archive(nid,ntime,'inertiedat',
465     &     'Soil thermal inertia',
466     &     'J.s-1/2.m-2.K-1',-3,ithS)
467
468! Write (0D) volumetric heat capacity (stored in comsoil.h)
469!      call write_archive(nid,ntime,'volcapa',
470!     &     'Soil volumetric heat capacity',
471!     &     'J.m-3.K-1',0,volcapa)
472! Note: no need to write volcapa, it is stored in "controle" table
473
474c-----------------------------------------------------------------------
475c Ecriture du champs  cloudfrac,hice,totalcloudfrac
476c-----------------------------------------------------------------------
477      call write_archive(nid,ntime,'hice',
478     &         'Height of oceanic ice','m',2,hiceS)
479      call write_archive(nid,ntime,'totalcloudfrac',
480     &        'Total cloud Fraction','',2,totalcloudfracS)
481      call write_archive(nid,ntime,'cloudfrac'
482     &        ,'Cloud fraction','',3,cloudfracS)
483
484c-----------------------------------------------------------------------
485c Slab ocean
486c-----------------------------------------------------------------------
487      OPEN(99,file='callphys.def',status='old',form='formatted'
488     &     ,iostat=ierr)
489      CLOSE(99)
490
491      IF(ierr.EQ.0) THEN
492
493
494         write(*,*) "Use slab-ocean ?"
495         ok_slab_ocean=.false.         ! default value
496         call getin("ok_slab_ocean",ok_slab_ocean)
497         write(*,*) "ok_slab_ocean = ",ok_slab_ocean
498
499      if(ok_slab_ocean) then
500      call write_archive(nid,ntime,'rnat'
501     &        ,'rnat','',2,rnatS)
502      call write_archive(nid,ntime,'pctsrf_sic'
503     &        ,'pctsrf_sic','',2,pctsrf_sicS)
504      call write_archive(nid,ntime,'sea_ice'
505     &        ,'sea_ice','',2,sea_iceS)
506      call write_archive(nid,ntime,'tslab'
507     &        ,'tslab','',3,tslabS)
508      call write_archive(nid,ntime,'tsea_ice'
509     &        ,'tsea_ice','',2,tsea_iceS)
510      endif !ok_slab_ocean
511      ENDIF
512c-----------------------------------------------------------------------
513c Fin 
514c-----------------------------------------------------------------------
515      ierr=NF_CLOSE(nid)
516
517      write(*,*) "start2archive: All is well that ends well."
518
519      end 
Note: See TracBrowser for help on using the repository browser.