source: trunk/LMDZ.MARS/libf/dynphy_lonlat/phymars/start2archive_SSO.F @ 3094

Last change on this file since 3094 was 2999, checked in by llange, 18 months ago

Mars PCM
Include perenial_co2ice (equivalent of watercap) to distinguich between CO2 frost and perenial CO2 ice for paleoclimate studies.
When no frost is present and we dig into perenial ice, the surface albedo is changed. The albedo for seasonal ice is set to 0.65, and the perenial ice albedo can be fixed in the callphys.def. I recommand values between 0.8 and 0.9.
To use this, paleoclimate must be set to True and TESalbedo to false in the callphys.def. Else, it runs as usual with TES albedo
LL

File size: 19.8 KB
Line 
1c=======================================================================
2      PROGRAM start2archive_SSO
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: infotrac_init, nqtot, tname
22      use comsoil_h, only: nsoilmx, inertiedat,inertiesoil
23      use surfdat_h, only: ini_surfdat_h, qsurf
24!      use comgeomphy, only: initcomgeomphy
25      use filtreg_mod, only: inifilr
26      USE mod_const_mpi, ONLY: COMM_LMDZ
27      use control_mod, only: planet_type
28      USE comvert_mod, ONLY: ap,bp
29      USE comconst_mod, ONLY: daysec,dtphys,rad,g,r,cpp
30      USE temps_mod, ONLY: day_ini,hour_ini
31      USE iniphysiq_mod, ONLY: iniphysiq
32      USE phyetat0_mod, ONLY: phyetat0
33      USE exner_hyb_m, ONLY: exner_hyb
34      use comslope_mod, ONLY: nslope,def_slope,def_slope_mean,
35     &                        subslope_dist
36      USE comcstfi_h, only: pi
37! AD: SSO parameters
38      USE surfdat_h, ONLY: phisfi, albedodat, z0, z0_default,
39     &    zmea, zstd, zsig, zgam, zthe, hmons, summit, base
40      implicit none
41
42      include "dimensions.h"
43      integer, parameter :: ngridmx = (2+(jjm-1)*iim - 1/jjm)
44      include "paramet.h"
45      include "comdissip.h"
46      include "comgeom.h"
47      include "netcdf.inc"
48
49c-----------------------------------------------------------------------
50c   Declarations
51c-----------------------------------------------------------------------
52
53c variables dynamiques du GCM
54c -----------------------------
55      REAL vcov(ip1jm,llm),ucov(ip1jmp1,llm) ! vents covariants
56      REAL teta(ip1jmp1,llm)                    ! temperature potentielle
57      REAL,ALLOCATABLE :: q(:,:,:)   ! champs advectes
58      REAL pks(ip1jmp1)                      ! exner (f pour filtre)
59      REAL pk(ip1jmp1,llm)
60      REAL pkf(ip1jmp1,llm)
61      REAL phis(ip1jmp1)                     ! geopotentiel au sol
62      REAL masse(ip1jmp1,llm)                ! masse de l'atmosphere
63      REAL ps(ip1jmp1)                       ! pression au sol
64      REAL p3d(iip1, jjp1, llm+1)            ! pression aux interfaces
65     
66c Variable Physiques (grille physique)
67c ------------------------------------
68      REAL,ALLOCATABLE :: tsurf(:,:)        ! Surface temperature
69      REAL,ALLOCATABLE :: tsoil(:,:,:) ! Soil temperature
70      REAL,ALLOCATABLE :: watercap(:,:)        ! h2o ice layer
71      REAL,ALLOCATABLE :: perenial_co2ice(:,:)        ! co2 ice layer
72      REAL tauscaling(ngridmx) ! dust conversion factor
73      REAL totcloudfrac(ngridmx) ! sub-grid cloud fraction
74      REAL q2(ngridmx,llm+1)
75      REAL,ALLOCATABLE :: emis(:,:)
76      REAL,ALLOCATABLE :: albedo(:,:,:)
77      REAL wstar(ngridmx)
78      DOUBLE PRECISION mem_Nccn_co2(ngridmx,llm)
79      DOUBLE PRECISION mem_Mccn_co2(ngridmx,llm)
80      DOUBLE PRECISION mem_Mh2o_co2(ngridmx,llm)
81      INTEGER start,length
82      PARAMETER (length = 100)
83      REAL tab_cntrl_fi(length) ! tableau des parametres de startfi
84      INTEGER*4 day_ini_fi
85
86c Variable naturelle / grille scalaire
87c ------------------------------------
88      REAL T(ip1jmp1,llm),us(ip1jmp1,llm),vs(ip1jmp1,llm)
89      REAL,ALLOCATABLE :: tsurfS(:,:)
90      REAL,ALLOCATABLE :: tsoilS(:,:,:)
91      REAL,ALLOCATABLE :: inertiesoilS(:,:,:)! Variable Soil Thermal Inertia  (obtained from PEM)
92      REAL ithS(ip1jmp1,nsoilmx) ! Soil Thermal Inertia for inertie dat (present day climate)
93      REAL,ALLOCATABLE :: watercapS(:,:)
94      REAL,ALLOCATABLE :: perenial_co2iceS(:,:)        ! co2 ice layer
95      REAL tauscalingS(ip1jmp1)
96      REAL totcloudfracS(ip1jmp1)
97      REAL q2S(ip1jmp1,llm+1)
98      REAL,ALLOCATABLE :: qsurfS(:,:,:)
99      REAL,ALLOCATABLE :: emisS(:,:)
100      REAL,ALLOCATABLE :: albedoS(:,:)
101      REAL, ALLOCATABLE :: subslope_distS(:,:)
102
103! AD: SSO parameters
104      REAL zmeaS(ip1jmp1)
105      REAL zsigS(ip1jmp1)
106      REAL zstdS(ip1jmp1)
107      REAL zgamS(ip1jmp1)
108      REAL ztheS(ip1jmp1)
109      REAL albedodatS(ip1jmp1)
110      REAL z0S(ip1jmp1)
111      REAL hmonsS(ip1jmp1)
112      REAL summitS(ip1jmp1)
113      REAL baseS(ip1jmp1)
114
115c Variables intermediaires : vent naturel, mais pas coord scalaire
116c----------------------------------------------------------------
117      REAL vn(ip1jm,llm),un(ip1jmp1,llm)
118
119c Autres  variables
120c -----------------
121      LOGICAL startdrs
122      INTEGER Lmodif
123
124      REAL ptotal, co2icetotal
125      REAL timedyn,timefi !fraction du jour dans start, startfi
126      REAL date
127
128      CHARACTER*2 str2
129      CHARACTER*80 fichier
130      data  fichier /'startfi'/
131
132      INTEGER ij, l,i,j,isoil,iq,islope
133      character*80      fichnom
134      integer :: ierr,ntime
135      integer :: igcm_co2
136      integer :: nq,numvanle
137      character(len=30) :: txt ! to store some text
138
139c Netcdf
140c-------
141      integer varid,dimid,timelen
142      INTEGER nid,nid1
143
144c-----------------------------------------------------------------------
145c   Initialisations
146c-----------------------------------------------------------------------
147
148      CALL defrun_new(99, .TRUE. )
149
150      planet_type='mars'
151
152c=======================================================================
153c Lecture des donnees
154c=======================================================================
155! Load tracer number and names:
156      call infotrac_init
157
158! allocate arrays:
159      allocate(q(ip1jmp1,llm,nqtot))     
160
161      fichnom = 'start.nc'
162      CALL dynetat0(fichnom,vcov,ucov,teta,q,masse,
163     .       ps,phis,timedyn)
164
165c-----------------------------------------------------------------------
166c   Initialisations
167c-----------------------------------------------------------------------
168
169      CALL defrun_new(99, .FALSE. )
170      call iniconst
171      call inigeom
172      call inifilr
173
174! Initialize the physics
175         CALL iniphysiq(iim,jjm,llm,
176     &                  (jjm-1)*iim+2,comm_lmdz,
177     &                  daysec,day_ini,dtphys,
178     &                  rlatu,rlatv,rlonu,rlonv,
179     &                  aire,cu,cv,rad,g,r,cpp,
180     &                  1)
181
182      fichnom = 'startfi.nc'
183      Lmodif=0
184
185      allocate(tsurf(ngridmx,nslope))
186      allocate(tsoil(ngridmx,nsoilmx,nslope))
187      allocate(watercap(ngridmx,nslope))
188      allocate(perenial_co2ice(ngridmx,nslope))
189      allocate(emis(ngridmx,nslope))
190      allocate(albedo(ngridmx,2,nslope))
191
192      allocate(qsurfS(ip1jmp1,nqtot,nslope))
193      allocate(tsurfS(ip1jmp1,nslope))
194      allocate(tsoilS(ip1jmp1,nsoilmx,nslope))
195      allocate(inertiesoilS(ip1jmp1,nsoilmx,nslope))
196      allocate(watercapS(ip1jmp1,nslope))
197      allocate(perenial_co2iceS(ngridmx,nslope))
198      allocate(emisS(ip1jmp1,nslope))
199      allocate(albedoS(ip1jmp1,nslope))
200      allocate(subslope_distS(ip1jmp1,nslope))
201
202      CALL phyetat0 (fichnom,0,Lmodif,nsoilmx,ngridmx,llm,nqtot,
203     &      day_ini_fi,timefi,tsurf,tsoil,albedo,emis,q2,qsurf,
204     &      tauscaling,totcloudfrac,wstar,watercap,perenial_co2ice,
205     &      def_slope,def_slope_mean,subslope_dist)
206
207       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
208       IF (ierr.NE.NF_NOERR) THEN
209         write(6,*)' Pb d''ouverture du fichier'//fichnom
210        CALL ABORT
211       ENDIF
212                                               
213      ierr = NF_INQ_VARID (nid1, "controle", varid)
214      IF (ierr .NE. NF_NOERR) THEN
215       PRINT*, "start2archive: Le champ <controle> est absent"
216       CALL abort
217      ENDIF
218#ifdef NC_DOUBLE
219       ierr = NF_GET_VAR_DOUBLE(nid1, varid, tab_cntrl_fi)
220#else
221      ierr = NF_GET_VAR_REAL(nid1, varid, tab_cntrl_fi)
222#endif
223       IF (ierr .NE. NF_NOERR) THEN
224          PRINT*, "start2archive: Lecture echoue pour <controle>"
225          CALL abort
226       ENDIF
227
228      ierr = NF_CLOSE(nid1)
229
230c-----------------------------------------------------------------------
231c Controle de la synchro
232c-----------------------------------------------------------------------
233!mars a voir      if ((day_ini_fi.ne.day_ini).or.(abs(timefi-timedyn).gt.1.e-10))
234      if ((mod(day_ini_fi,669).ne.mod(day_ini,669)))
235     &  stop ' Probleme de Synchro entre start et startfi !!!'
236
237
238c *****************************************************************
239c    Option : Reinitialisation des dates dans la premieres annees :
240       do while (day_ini.ge.669)
241          day_ini=day_ini-669
242       enddo
243c *****************************************************************
244
245      CALL pression(ip1jmp1, ap, bp, ps, p3d)
246      call exner_hyb(ip1jmp1, ps, p3d, pks, pk, pkf)
247
248c=======================================================================
249c Transformation EN VARIABLE NATURELLE / GRILLE SCALAIRE si necessaire
250c=======================================================================
251c  Les variables modeles dependent de la resolution. Il faut donc
252c  eliminer les facteurs responsables de cette dependance
253c  (pour utiliser newstart)
254c=======================================================================
255
256c-----------------------------------------------------------------------
257c Vent   (depend de la resolution horizontale)
258c-----------------------------------------------------------------------
259c
260c ucov --> un  et  vcov --> vn
261c un --> us  et   vn --> vs
262c
263c-----------------------------------------------------------------------
264
265      call covnat(llm,ucov, vcov, un, vn)
266      call wind_scal(un,vn,us,vs)
267
268c-----------------------------------------------------------------------
269c Temperature  (depend de la resolution verticale => de "sigma.def")
270c-----------------------------------------------------------------------
271c
272c h --> T
273c
274c-----------------------------------------------------------------------
275
276      DO l=1,llm
277         DO ij=1,ip1jmp1
278            T(ij,l)=teta(ij,l)*pk(ij,l)/cpp !mars deduit de l'equation dans newstart
279         ENDDO
280      ENDDO
281
282c-----------------------------------------------------------------------
283c Variable physique
284c-----------------------------------------------------------------------
285c
286c tsurf --> tsurfS
287c tsoil --> tsoilS
288c inertiesoil ---> inertiesoilS
289c emis --> emisS
290c q2 --> q2S
291c qsurf --> qsurfS
292c tauscaling --> tauscalingS
293c totcloudfrac --> totcloudfracS
294c
295c-----------------------------------------------------------------------
296
297      do islope=1,nslope
298      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tsurf(:,islope),
299     &    tsurfS(:,islope))
300      call gr_fi_dyn(1,ngridmx,iip1,jjp1,watercap(:,islope),
301     &    watercapS(:,islope))
302      call gr_fi_dyn(1,ngridmx,iip1,jjp1,perenial_co2ice(:,islope),
303     &    perenial_co2iceS(:,islope))
304      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,tsoil(:,:,islope),
305     &    tsoilS(:,:,islope))
306      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,inertiesoil(:,:,islope),
307     &    inertiesoilS(:,:,islope))
308      ! Note: thermal inertia "inertiedat" is in comsoil.h
309      call gr_fi_dyn(1,ngridmx,iip1,jjp1,emis(:,islope),
310     &     emisS(:,islope))
311      call gr_fi_dyn(1,ngridmx,iip1,jjp1,albedo(:,1,islope),
312     &   albedoS(:,islope))
313      call gr_fi_dyn(nqtot,ngridmx,iip1,jjp1,qsurf(:,:,islope),
314     &   qsurfS(:,:,islope))
315      call gr_fi_dyn(1,ngridmx,iip1,jjp1,subslope_dist(:,islope),
316     &    subslope_distS(:,islope))
317      enddo
318
319      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,inertiedat,ithS)
320      call gr_fi_dyn(llm+1,ngridmx,iip1,jjp1,q2,q2S)
321      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tauscaling,tauscalingS)
322      call gr_fi_dyn(1,ngridmx,iip1,jjp1,totcloudfrac,totcloudfracS)
323
324! AD: for SSO parameters
325      call gr_fi_dyn(1,ngridmx,iip1,jjp1,zmea,zmeaS)
326      call gr_fi_dyn(1,ngridmx,iip1,jjp1,zstd,zstdS)
327      call gr_fi_dyn(1,ngridmx,iip1,jjp1,zsig,zsigS)
328      call gr_fi_dyn(1,ngridmx,iip1,jjp1,zthe,ztheS)
329      call gr_fi_dyn(1,ngridmx,iip1,jjp1,zgam,zgamS)
330      call gr_fi_dyn(1,ngridmx,iip1,jjp1,albedodat,albedodatS)
331      call gr_fi_dyn(1,ngridmx,iip1,jjp1,z0,z0S)
332      call gr_fi_dyn(1,ngridmx,iip1,jjp1,hmons,hmonsS)
333      call gr_fi_dyn(1,ngridmx,iip1,jjp1,summit,summitS)
334      call gr_fi_dyn(1,ngridmx,iip1,jjp1,base,baseS)
335
336c=======================================================================
337c Info pour controler
338c=======================================================================
339
340      DO iq=1,nqtot
341        if (trim(tname(iq)) .eq. "co2") then
342           igcm_co2=iq
343        endif
344      enddo
345
346      ptotal =  0.
347      co2icetotal = 0.
348      DO j=1,jjp1
349         DO i=1,iim
350           DO islope=1,nslope
351           ptotal=ptotal+aire(i+(iim+1)*(j-1))*ps(i+(iim+1)*(j-1))/g
352           co2icetotal = co2icetotal +
353     &        qsurfS(i+(iim+1)*(j-1),igcm_co2,islope)*
354     &        aire(i+(iim+1)*(j-1))*
355     &    subslope_distS(i+(iim+1)*(j-1),islope)/
356     &    cos(pi*def_slope_mean(islope))
357           ENDDO
358         ENDDO
359      ENDDO
360      write(*,*)'Ancienne grille : masse de l''atm :',ptotal
361      write(*,*)'Ancienne grille : masse de la glace CO2 :',co2icetotal
362
363c-----------------------------------------------------------------------
364c Passage de "ptotal" et "co2icetotal" par tab_cntrl_fi
365c-----------------------------------------------------------------------
366
367      tab_cntrl_fi(49) = ptotal
368      tab_cntrl_fi(50) = co2icetotal
369
370c=======================================================================
371c Ecriture dans le fichier  "start_archive"
372c=======================================================================
373
374c-----------------------------------------------------------------------
375c Ouverture de "start_archive"
376c-----------------------------------------------------------------------
377
378      ierr = NF_OPEN ('start_archive.nc', NF_WRITE,nid)
379 
380c-----------------------------------------------------------------------
381c  si "start_archive" n'existe pas:
382c    1_ ouverture
383c    2_ creation de l'entete dynamique ("ini_archive")
384c-----------------------------------------------------------------------
385c ini_archive:
386c On met dans l'entete le tab_cntrl dynamique (1 a 16)
387c  On y ajoute les valeurs du tab_cntrl_fi (a partir de 51)
388c  En plus les deux valeurs ptotal et co2icetotal (99 et 100)
389c-----------------------------------------------------------------------
390
391      if (ierr.ne.NF_NOERR) then
392         write(*,*)'OK, Could not open file "start_archive.nc"'
393         write(*,*)'So let s create a new "start_archive"'
394         ierr = NF_CREATE('start_archive.nc',
395     &  IOR(NF_CLOBBER,NF_64BIT_OFFSET), nid)
396         call ini_archive(nid,day_ini,phis,ithS,tab_cntrl_fi,
397     &         def_slope,subslope_distS)
398      endif
399
400c-----------------------------------------------------------------------
401c Ecriture de la coordonnee temps (date en jours)
402c-----------------------------------------------------------------------
403
404      date = day_ini + hour_ini
405      ierr= NF_INQ_VARID(nid,"Time",varid)
406      ierr= NF_INQ_DIMID(nid,"Time",dimid)
407      ierr= NF_INQ_DIMLEN(nid,dimid,timelen)
408      ntime=timelen+1
409
410      write(*,*) "******************"
411      write(*,*) "ntime",ntime
412      write(*,*) "******************"
413#ifdef NC_DOUBLE
414      ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
415#else
416      ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
417#endif
418      if (ierr.ne.NF_NOERR) then
419         write(*,*) "time matter ",NF_STRERROR(ierr)
420         stop
421      endif
422
423c-----------------------------------------------------------------------
424c Ecriture des champs  (co2ice,emis,ps,Tsurf,T,u,v,q2,q,qsurf)
425c-----------------------------------------------------------------------
426c ATTENTION: q2 a une couche de plus!!!!
427c    Pour creer un fichier netcdf lisible par grads,
428c    On passe donc une des couches de q2 a part
429c    comme une variable 2D (la couche au sol: "q2surf")
430c    Les lmm autres couches sont nommees "q2atm" (3D)
431c-----------------------------------------------------------------------
432
433      call write_archive(nid,ntime,'watercap','couche de glace h2o',
434     &  'kg/m2',2,watercapS)
435      call write_archive(nid,ntime,'perenial_co2ice','couche de glace co2',
436     &  'kg/m2',2,perenial_co2iceS)
437      call write_archive(nid,ntime,'tauscaling',
438     &  'dust conversion factor',' ',2,tauscalingS)
439      call write_archive(nid,ntime,'totcloudfrac',
440     &  'sub grid cloud fraction',' ',2,totcloudfracS)
441      call write_archive(nid,ntime,'emis','grd emis',' ',2,emisS)
442      call write_archive(nid,ntime,'albedo','surface albedo',' ',
443     &                             2,albedoS)
444      call write_archive(nid,ntime,'ps','Psurf','Pa',2,ps)
445      call write_archive(nid,ntime,'tsurf','surf T','K',2,tsurfS)
446      call write_archive(nid,ntime,'temp','temperature','K',3,t)
447      call write_archive(nid,ntime,'u','Vent zonal','m.s-1',3,us)
448      call write_archive(nid,ntime,'v','Vent merid','m.s-1',3,vs)
449      call write_archive(nid,ntime,'q2surf','wind variance','m2.s-2',2,
450     .              q2S)
451      call write_archive(nid,ntime,'q2atm','wind variance','m2.s-2',3,
452     .              q2S(1,2))
453! AD: SSO parameters
454      call write_archive(nid,ntime,'ZMEA','zmea',' ',2,zmeaS)
455      call write_archive(nid,ntime,'ZSTD','zstd',' ',2,zstdS)
456      call write_archive(nid,ntime,'ZSIG','zsig',' ',2,zsigS)
457      call write_archive(nid,ntime,'ZTHE','zthe',' ',2,ztheS)
458      call write_archive(nid,ntime,'ZGAM','zgam',' ',2,zgamS)
459      call write_archive(nid,ntime,'albedodat','albedodat',
460     &                             ' ',2,albedodatS)
461      call write_archive(nid,ntime,'z0','z0',' ',2,z0S)
462      call write_archive(nid,ntime,'summit','summit',
463     &                             ' ',2,summitS)
464      call write_archive(nid,ntime,'hmons','hmons',' ',2,hmonsS)
465      call write_archive(nid,ntime,'base','base',' ',2,baseS)
466c-----------------------------------------------------------------------
467c Ecriture du champs  q  ( q[1,nqtot] )
468c-----------------------------------------------------------------------
469      do iq=1,nqtot
470c       write(str2,'(i2.2)') iq
471c        call write_archive(nid,ntime,'q'//str2,'tracer','kg/kg',
472c     .         3,q(1,1,iq))
473        call write_archive(nid,ntime,tname(iq),'tracer','kg/kg',
474     &         3,q(1,1,iq))
475      end do
476c-----------------------------------------------------------------------
477c Ecriture du champs  qsurf  ( qsurf[1,nqtot] )
478c-----------------------------------------------------------------------
479      do iq=1,nqtot
480c       write(str2,'(i2.2)') iq
481c       call write_archive(nid,ntime,'qsurf'//str2,'Tracer on surface',
482c     $  'kg.m-2',2,qsurfS(1,iq))
483        txt=trim(tname(iq))//"_surf"
484        call write_archive(nid,ntime,txt,'Tracer on surface',
485     &  'kg.m-2',2,qsurfS(:,iq,:))
486      enddo
487
488
489c-----------------------------------------------------------------------
490c Ecriture du champs  tsoil  ( Tg[1,10] )
491c-----------------------------------------------------------------------
492c "tsoil" Temperature au sol definie dans 10 couches dans le sol
493c   Les 10 couches sont lues comme 10 champs
494c  nommees Tg[1,10]
495
496c      do isoil=1,nsoilmx
497c       write(str2,'(i2.2)') isoil
498c       call write_archive(nid,ntime,'Tg'//str2,'Ground Temperature ',
499c     .   'K',2,tsoilS(1,isoil))
500c      enddo
501
502! Write soil temperatures tsoil
503      call write_archive(nid,ntime,'tsoil','Soil temperature',
504     &     'K',-3,tsoilS(:,:,:))
505
506! Write soil thermal inertia
507      call write_archive(nid,ntime,'inertiesoil','Soil TI',
508     &     'J.s-1/2.m-2.K-1',-3,inertiesoilS(:,:,:))
509! Write soil thermal inertia for current climate
510      call write_archive(nid,ntime,'inertiedat',
511     &     'Soil thermal inertia',
512     &     'J.s-1/2.m-2.K-1',-3,ithS)
513
514! Write (0D) volumetric heat capacity (stored in comsoil.h)
515!      call write_archive(nid,ntime,'volcapa',
516!     &     'Soil volumetric heat capacity',
517!     &     'J.m-3.K-1',0,volcapa)
518! Note: no need to write volcapa, it is stored in "controle" table
519
520      ierr=NF_CLOSE(nid)
521c-----------------------------------------------------------------------
522c Fin
523c-----------------------------------------------------------------------
524
525      write(*,*) "startarchive: all is well that ends well"
526     
527      end
Note: See TracBrowser for help on using the repository browser.