source: trunk/LMDZ.GENERIC/libf/dynphy_lonlat/phystd/start2archive.F @ 2613

Last change on this file since 2613 was 2354, checked in by emillour, 5 years ago

Generic GCM:
Major cleanup: remove obsolete compilation scripts (makegcm*) and old dynamical
core, as it is obsolete with respect to the one provide in LMDZ.COMMON.
EM

File size: 20.4 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: infotrac_init, nqtot, tname
22      USE comsoil_h
23     
24      use slab_ice_h, only: noceanmx
25      USE ioipsl_getincom, only: getin
26      USE planete_mod, only: year_day
27      USE mod_const_mpi, ONLY: COMM_LMDZ
28      USE control_mod, only: planet_type
29      USE callkeys_mod, ONLY: ok_slab_ocean
30      use filtreg_mod, only: inifilr
31      USE comvert_mod, ONLY: ap,bp
32      USE comconst_mod, ONLY: daysec,dtphys,rad,g,r,cpp
33      USE temps_mod, ONLY: day_ini
34      USE iniphysiq_mod, ONLY: iniphysiq
35      use phys_state_var_mod, only: phys_state_var_init
36      use phyetat0_mod, only: phyetat0
37      use nonoro_gwd_ran_mod, only: du_nonoro_gwd, dv_nonoro_gwd,
38     &                          east_gwstress, west_gwstress
39      use exner_hyb_m, only: exner_hyb
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
48      include "netcdf.inc"
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 tsurf(ngridmx)        ! Surface temperature
69      REAL,ALLOCATABLE :: tsoil(:,:) ! Soil temperature
70      REAL co2ice(ngridmx)        ! CO2 ice layer
71      REAL q2(ngridmx,llm+1)
72      REAL,ALLOCATABLE :: qsurf(:,:)
73      REAL emis(ngridmx)
74      INTEGER start,length
75      PARAMETER (length = 100)
76      REAL tab_cntrl_fi(length) ! tableau des parametres de startfi
77      REAL tab_cntrl_dyn(length) ! tableau des parametres de start
78      INTEGER*4 day_ini_fi
79
80!     added by FF for cloud fraction setup
81      REAL hice(ngridmx)
82      REAL cloudfrac(ngridmx,llm),totalcloudfrac(ngridmx)
83
84!     added by BC for slab ocean
85      REAL rnat(ngridmx),pctsrf_sic(ngridmx),sea_ice(ngridmx)
86      REAL tslab(ngridmx,noceanmx),tsea_ice(ngridmx)
87
88
89c Variable naturelle / grille scalaire
90c ------------------------------------
91      REAL T(ip1jmp1,llm),us(ip1jmp1,llm),vs(ip1jmp1,llm)
92      REAL tsurfS(ip1jmp1)
93      REAL,ALLOCATABLE :: tsoilS(:,:)
94      REAL,ALLOCATABLE :: ithS(:,:) ! Soil Thermal Inertia
95      REAL co2iceS(ip1jmp1)
96      REAL q2S(ip1jmp1,llm+1)
97      REAL,ALLOCATABLE :: qsurfS(:,:)
98      REAL emisS(ip1jmp1)
99
100!     added by FF for cloud fraction setup
101      REAL hiceS(ip1jmp1)
102      REAL cloudfracS(ip1jmp1,llm),totalcloudfracS(ip1jmp1)
103
104!     added by BC for slab ocean
105      REAL rnatS(ip1jmp1),pctsrf_sicS(ip1jmp1),sea_iceS(ip1jmp1)
106      REAL tslabS(ip1jmp1,noceanmx),tsea_iceS(ip1jmp1)
107
108!     For non-orographic GW
109      REAL du_nonoro_gwdS(ip1jmp1,llm),dv_nonoro_gwdS(ip1jmp1,llm)
110      REAL east_gwstressS(ip1jmp1,llm),west_gwstressS(ip1jmp1,llm)
111
112c Variables intermediaires : vent naturel, mais pas coord scalaire
113c----------------------------------------------------------------
114      REAL vn(ip1jm,llm),un(ip1jmp1,llm)
115
116c Autres  variables
117c -----------------
118      LOGICAL startdrs
119      INTEGER Lmodif
120
121      REAL ptotal, co2icetotal
122      REAL timedyn,timefi !fraction du jour dans start, startfi
123      REAL date
124
125      CHARACTER*2 str2
126      CHARACTER*80 fichier
127      data  fichier /'startfi'/
128
129      INTEGER ij, l,i,j,isoil,iq
130      character*80      fichnom
131      integer :: ierr,ntime
132      integer :: nq,numvanle
133      character(len=30) :: txt ! to store some text
134
135c Netcdf
136c-------
137      integer varid,dimid,timelen
138      INTEGER nid,nid1
139
140c-----------------------------------------------------------------------
141c   Initialisations
142c-----------------------------------------------------------------------
143
144      CALL defrun_new(99, .TRUE. )
145
146      planet_type="generic"
147
148c=======================================================================
149c Lecture des donnees
150c=======================================================================
151! Load tracer number and names:
152      call infotrac_init
153
154! allocate arrays:
155      allocate(q(ip1jmp1,llm,nqtot))
156      allocate(qsurf(ngridmx,nqtot))
157      allocate(qsurfS(ip1jmp1,nqtot))
158! other array allocations:
159!      call ini_comsoil_h(ngridmx) ! done via iniphysiq
160
161      fichnom = 'start.nc'
162      CALL dynetat0(fichnom,vcov,ucov,teta,q,masse,
163     .       ps,phis,timedyn)
164
165! load 'controle' array from dynamics start file
166
167       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
168       IF (ierr.NE.NF_NOERR) THEN
169         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
170        CALL ABORT
171       ENDIF
172                                               
173      ierr = NF_INQ_VARID (nid1, "controle", varid)
174      IF (ierr .NE. NF_NOERR) THEN
175       PRINT*, "start2archive: Le champ <controle> est absent"
176       CALL abort
177      ENDIF
178#ifdef NC_DOUBLE
179       ierr = NF_GET_VAR_DOUBLE(nid1, varid, tab_cntrl_dyn)
180#else
181      ierr = NF_GET_VAR_REAL(nid1, varid, tab_cntrl_dyn)
182#endif
183       IF (ierr .NE. NF_NOERR) THEN
184          PRINT*, "start2archive: Lecture echoue pour <controle>"
185          CALL abort
186       ENDIF
187
188      ierr = NF_CLOSE(nid1)
189
190! Get value of the "subsurface_layers" dimension from physics start file
191      fichnom = 'startfi.nc'
192      ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
193       IF (ierr.NE.NF_NOERR) THEN
194         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
195        CALL ABORT
196       ENDIF
197      ierr = NF_INQ_DIMID(nid1,"subsurface_layers",varid)
198      IF (ierr .NE. NF_NOERR) THEN
199       PRINT*, "start2archive: No subsurface_layers dimension!!"
200       CALL abort
201      ENDIF
202      ierr = NF_INQ_DIMLEN(nid1,varid,nsoilmx)
203      IF (ierr .NE. NF_NOERR) THEN
204       PRINT*, "start2archive: Failed reading subsurface_layers value!!"
205       CALL abort
206      ENDIF
207      ierr = NF_CLOSE(nid1)
208     
209      ! allocate arrays of nsoilmx size
210      allocate(tsoil(ngridmx,nsoilmx))
211      allocate(tsoilS(ip1jmp1,nsoilmx))
212      allocate(ithS(ip1jmp1,nsoilmx))
213
214c-----------------------------------------------------------------------
215c   Initialisations
216c-----------------------------------------------------------------------
217
218      CALL defrun_new(99, .FALSE. )
219      call iniconst
220      call inigeom
221      call inifilr
222
223! Initialize the physics
224         CALL iniphysiq(iim,jjm,llm,
225     &                  (jjm-1)*iim+2,comm_lmdz,
226     &                  daysec,day_ini,dtphys,
227     &                  rlatu,rlatv,rlonu,rlonv,
228     &                  aire,cu,cv,rad,g,r,cpp,
229     &                  1)
230
231      fichnom = 'startfi.nc'
232      Lmodif=0
233
234! Allocate saved arrays (as in firstcall of physiq)
235      call phys_state_var_init(nqtot)
236     
237! Initialize tracer names, indexes and properties
238      CALL initracer(ngridmx,nqtot,tname)
239
240      CALL phyetat0(.true.,ngridmx,llm,fichnom,0,Lmodif,nsoilmx,nqtot,
241     .      day_ini_fi,timefi,
242     .      tsurf,tsoil,emis,q2,qsurf,
243!       change FF 05/2011
244     .       cloudfrac,totalcloudfrac,hice,
245!       change BC 05/2014
246     .       rnat,pctsrf_sic,tslab,tsea_ice,sea_ice)
247
248
249
250
251! load 'controle' array from physics start file
252
253       ierr = NF_OPEN (fichnom, NF_NOWRITE,nid1)
254       IF (ierr.NE.NF_NOERR) THEN
255         write(6,*)' Pb d''ouverture du fichier'//trim(fichnom)
256        CALL ABORT
257       ENDIF
258                                               
259      ierr = NF_INQ_VARID (nid1, "controle", varid)
260      IF (ierr .NE. NF_NOERR) THEN
261       PRINT*, "start2archive: Le champ <controle> est absent"
262       CALL abort
263      ENDIF
264#ifdef NC_DOUBLE
265       ierr = NF_GET_VAR_DOUBLE(nid1, varid, tab_cntrl_fi)
266#else
267      ierr = NF_GET_VAR_REAL(nid1, varid, tab_cntrl_fi)
268#endif
269       IF (ierr .NE. NF_NOERR) THEN
270          PRINT*, "start2archive: Lecture echoue pour <controle>"
271          CALL abort
272       ENDIF
273
274      ierr = NF_CLOSE(nid1)
275
276
277c-----------------------------------------------------------------------
278c Controle de la synchro
279c-----------------------------------------------------------------------
280!mars a voir      if ((day_ini_fi.ne.day_ini).or.(abs(timefi-timedyn).gt.1.e-10))
281      if ((day_ini_fi.ne.day_ini))
282     &  stop ' Probleme de Synchro entre start et startfi !!!'
283
284
285c *****************************************************************
286c    Option : Reinitialisation des dates dans la premieres annees :
287       do while (day_ini.ge.year_day)
288          day_ini=day_ini-year_day
289       enddo
290c *****************************************************************
291
292      CALL pression(ip1jmp1, ap, bp, ps, p3d)
293      call exner_hyb(ip1jmp1, ps, p3d, pks, pk, pkf)
294
295c=======================================================================
296c Transformation EN VARIABLE NATURELLE / GRILLE SCALAIRE si necessaire
297c=======================================================================
298c  Les variables modeles dependent de la resolution. Il faut donc
299c  eliminer les facteurs responsables de cette dependance
300c  (pour utiliser newstart)
301c=======================================================================
302
303c-----------------------------------------------------------------------
304c Vent   (depend de la resolution horizontale)
305c-----------------------------------------------------------------------
306c
307c ucov --> un  et  vcov --> vn
308c un --> us  et   vn --> vs
309c
310c-----------------------------------------------------------------------
311
312      call covnat(llm,ucov, vcov, un, vn)
313      call wind_scal(un,vn,us,vs)
314
315c-----------------------------------------------------------------------
316c Temperature  (depend de la resolution verticale => de "sigma.def")
317c-----------------------------------------------------------------------
318c
319c h --> T
320c
321c-----------------------------------------------------------------------
322
323      DO l=1,llm
324         DO ij=1,ip1jmp1
325            T(ij,l)=teta(ij,l)*pk(ij,l)/cpp !mars deduit de l'equation dans newstart
326         ENDDO
327      ENDDO
328
329c-----------------------------------------------------------------------
330c Variable physique
331c-----------------------------------------------------------------------
332c
333c tsurf --> tsurfS
334c co2ice --> co2iceS
335c tsoil --> tsoilS
336c emis --> emisS
337c q2 --> q2S
338c qsurf --> qsurfS
339c
340c-----------------------------------------------------------------------
341
342      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tsurf,tsurfS)
343!      call gr_fi_dyn(1,ngridmx,iip1,jjp1,co2ice,co2iceS)
344      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,tsoil,tsoilS)
345      ! Note: thermal inertia "inertiedat" is in comsoil.h
346      call gr_fi_dyn(nsoilmx,ngridmx,iip1,jjp1,inertiedat,ithS)
347      call gr_fi_dyn(1,ngridmx,iip1,jjp1,emis,emisS)
348      call gr_fi_dyn(llm+1,ngridmx,iip1,jjp1,q2,q2S)
349      call gr_fi_dyn(nqtot,ngridmx,iip1,jjp1,qsurf,qsurfS)
350      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,cloudfrac,cloudfracS)
351      call gr_fi_dyn(1,ngridmx,iip1,jjp1,hice,hiceS)
352      call gr_fi_dyn(1,ngridmx,iip1,jjp1,totalcloudfrac,totalcloudfracS)
353
354      call gr_fi_dyn(1,ngridmx,iip1,jjp1,rnat,rnatS)
355      call gr_fi_dyn(1,ngridmx,iip1,jjp1,pctsrf_sic,pctsrf_sicS)
356      call gr_fi_dyn(1,ngridmx,iip1,jjp1,tsea_ice,tsea_iceS)
357      call gr_fi_dyn(1,ngridmx,iip1,jjp1,sea_ice,sea_iceS)
358      call gr_fi_dyn(noceanmx,ngridmx,iip1,jjp1,tslab,tslabS)
359
360      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,du_nonoro_gwd,du_nonoro_gwdS)
361      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,dv_nonoro_gwd,dv_nonoro_gwdS)
362      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,east_gwstress,east_gwstressS)
363      call gr_fi_dyn(llm,ngridmx,iip1,jjp1,west_gwstress,west_gwstressS)
364c=======================================================================
365c Info pour controler
366c=======================================================================
367
368      ptotal =  0.
369      co2icetotal = 0.
370      DO j=1,jjp1
371         DO i=1,iim
372           ptotal=ptotal+aire(i+(iim+1)*(j-1))*ps(i+(iim+1)*(j-1))/g
373!           co2icetotal = co2icetotal +
374!     &            co2iceS(i+(iim+1)*(j-1))*aire(i+(iim+1)*(j-1))
375         ENDDO
376      ENDDO
377      write(*,*)'Old grid: : atmospheric mass :',ptotal
378!      write(*,*)'Ancienne grille : masse de la glace CO2 :',co2icetotal
379
380c-----------------------------------------------------------------------
381c Passage de "ptotal" et "co2icetotal" par tab_cntrl_fi
382c-----------------------------------------------------------------------
383
384      tab_cntrl_fi(49) = ptotal
385      tab_cntrl_fi(50) = co2icetotal
386
387c=======================================================================
388c Ecriture dans le fichier  "start_archive"
389c=======================================================================
390
391c-----------------------------------------------------------------------
392c Ouverture de "start_archive"
393c-----------------------------------------------------------------------
394
395      ierr = NF_OPEN ('start_archive.nc', NF_WRITE,nid)
396 
397c-----------------------------------------------------------------------
398c  si "start_archive" n'existe pas:
399c    1_ ouverture
400c    2_ creation de l'entete dynamique ("ini_archive")
401c-----------------------------------------------------------------------
402c ini_archive:
403c On met dans l'entete le tab_cntrl dynamique (1 a 16)
404c  On y ajoute les valeurs du tab_cntrl_fi (a partir de 51)
405c  En plus les deux valeurs ptotal et co2icetotal (99 et 100)
406c-----------------------------------------------------------------------
407
408      if (ierr.ne.NF_NOERR) then
409         write(*,*)'OK, Could not open file "start_archive.nc"'
410         write(*,*)'So let s create a new "start_archive"'
411         ierr = NF_CREATE('start_archive.nc', NF_CLOBBER, nid)
412         call ini_archive(nid,day_ini,phis,ithS,tab_cntrl_fi,
413     &                                          tab_cntrl_dyn)
414      endif
415
416c-----------------------------------------------------------------------
417c Ecriture de la coordonnee temps (date en jours)
418c-----------------------------------------------------------------------
419
420      date = day_ini
421      ierr= NF_INQ_VARID(nid,"Time",varid)
422      ierr= NF_INQ_DIMID(nid,"Time",dimid)
423      ierr= NF_INQ_DIMLEN(nid,dimid,timelen)
424      ntime=timelen+1
425
426      write(*,*) "******************"
427      write(*,*) "ntime",ntime
428      write(*,*) "******************"
429#ifdef NC_DOUBLE
430      ierr= NF_PUT_VARA_DOUBLE(nid,varid,ntime,1,date)
431#else
432      ierr= NF_PUT_VARA_REAL(nid,varid,ntime,1,date)
433#endif
434      if (ierr.ne.NF_NOERR) then
435         write(*,*) "time matter ",NF_STRERROR(ierr)
436         stop
437      endif
438
439c-----------------------------------------------------------------------
440c Ecriture des champs  (co2ice,emis,ps,Tsurf,T,u,v,q2,q,qsurf)
441c-----------------------------------------------------------------------
442c ATTENTION: q2 a une couche de plus!!!!
443c    Pour creer un fichier netcdf lisible par grads,
444c    On passe donc une des couches de q2 a part
445c    comme une variable 2D (la couche au sol: "q2surf")
446c    Les lmm autres couches sont nommees "q2atm" (3D)
447c-----------------------------------------------------------------------
448
449!      call write_archive(nid,ntime,'co2ice','couche de glace co2',
450!     &  'kg/m2',2,co2iceS)
451      call write_archive(nid,ntime,'emis','grd emis',' ',2,emisS)
452      call write_archive(nid,ntime,'ps','Psurf','Pa',2,ps)
453      call write_archive(nid,ntime,'tsurf','surf T','K',2,tsurfS)
454      call write_archive(nid,ntime,'temp','temperature','K',3,t)
455      call write_archive(nid,ntime,'u','Vent zonal','m.s-1',3,us)
456      call write_archive(nid,ntime,'v','Vent merid','m.s-1',3,vs)
457      call write_archive(nid,ntime,'q2surf','wind variance','m2.s-2',2,
458     .              q2S)
459      call write_archive(nid,ntime,'q2atm','wind variance','m2.s-2',3,
460     .              q2S(1,2))
461
462c-----------------------------------------------------------------------
463c Ecriture du champs  q  ( q[1,nqtot] )
464c-----------------------------------------------------------------------
465      do iq=1,nqtot
466        call write_archive(nid,ntime,tname(iq),'tracer','kg/kg',
467     &         3,q(1,1,iq))
468      end do
469c-----------------------------------------------------------------------
470c Ecriture du champs  qsurf  ( qsurf[1,nqtot] )
471c-----------------------------------------------------------------------
472      do iq=1,nqtot
473        txt=trim(tname(iq))//"_surf"
474        call write_archive(nid,ntime,txt,'Tracer on surface',
475     &  'kg.m-2',2,qsurfS(1,iq))
476      enddo
477
478
479c-----------------------------------------------------------------------
480c Ecriture du champs  tsoil  ( Tg[1,10] )
481c-----------------------------------------------------------------------
482c "tsoil" Temperature au sol definie dans 10 couches dans le sol
483c   Les 10 couches sont lues comme 10 champs
484c  nommees Tg[1,10]
485
486c      do isoil=1,nsoilmx
487c       write(str2,'(i2.2)') isoil
488c       call write_archive(nid,ntime,'Tg'//str2,'Ground Temperature ',
489c     .   'K',2,tsoilS(1,isoil))
490c      enddo
491
492! Write soil temperatures tsoil
493      call write_archive(nid,ntime,'tsoil','Soil temperature',
494     &     'K',-3,tsoilS)
495
496! Write soil thermal inertia
497      call write_archive(nid,ntime,'inertiedat',
498     &     'Soil thermal inertia',
499     &     'J.s-1/2.m-2.K-1',-3,ithS)
500
501! Write (0D) volumetric heat capacity (stored in comsoil.h)
502!      call write_archive(nid,ntime,'volcapa',
503!     &     'Soil volumetric heat capacity',
504!     &     'J.m-3.K-1',0,volcapa)
505! Note: no need to write volcapa, it is stored in "controle" table
506
507c-----------------------------------------------------------------------
508c Ecriture du champs  cloudfrac,hice,totalcloudfrac
509c-----------------------------------------------------------------------
510      call write_archive(nid,ntime,'hice',
511     &         'Height of oceanic ice','m',2,hiceS)
512      call write_archive(nid,ntime,'totalcloudfrac',
513     &        'Total cloud Fraction','',2,totalcloudfracS)
514      call write_archive(nid,ntime,'cloudfrac'
515     &        ,'Cloud fraction','',3,cloudfracS)
516
517c-----------------------------------------------------------------------
518c Slab ocean
519c-----------------------------------------------------------------------
520      OPEN(99,file='callphys.def',status='old',form='formatted'
521     &     ,iostat=ierr)
522      CLOSE(99)
523
524      IF(ierr.EQ.0) THEN
525
526        write(*,*) "Use slab-ocean ?"
527        ok_slab_ocean=.false.         ! default value
528        call getin("ok_slab_ocean",ok_slab_ocean)
529        write(*,*) "ok_slab_ocean = ",ok_slab_ocean
530
531        if(ok_slab_ocean) then
532          call write_archive(nid,ntime,'rnat'
533     &            ,'rnat','',2,rnatS)
534          call write_archive(nid,ntime,'pctsrf_sic'
535     &            ,'pctsrf_sic','',2,pctsrf_sicS)
536          call write_archive(nid,ntime,'sea_ice'
537     &            ,'sea_ice','',2,sea_iceS)
538          call write_archive(nid,ntime,'tslab'
539     &            ,'tslab','',-2,tslabS)
540          call write_archive(nid,ntime,'tsea_ice'
541     &            ,'tsea_ice','',2,tsea_iceS)
542        endif !ok_slab_ocean
543     
544      ENDIF ! of IF(ierr.EQ.0)
545
546! Non-orographic gavity waves
547      call write_archive(nid,ntime,"du_nonoro_gwd",
548     &     "Zonal wind tendency due to GW",'m.s-1',3,du_nonoro_gwdS)
549      call write_archive(nid,ntime,"dv_nonoro_gwd",
550     &     "Meridional wind tendency due to GW",'m.s-1',
551     &     3,dv_nonoro_gwdS)
552      call write_archive(nid,ntime,"east_gwstress",
553     &     "Eastward stress profile due to GW",'kg.m-1.s-2',
554     &     3,east_gwstressS)
555      call write_archive(nid,ntime,"west_gwstress",
556     &     "Westward stress profile due to GW",'kg.m-1.s-2',
557     &     3,west_gwstressS)
558
559c-----------------------------------------------------------------------
560c Fin
561c-----------------------------------------------------------------------
562      ierr=NF_CLOSE(nid)
563
564      write(*,*) "start2archive: All is well that ends well."
565
566      end
Note: See TracBrowser for help on using the repository browser.