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

Last change on this file since 1543 was 1543, checked in by emillour, 9 years ago

All models: Further adaptations to keep up with changes in LMDZ5 concerning
physics/dynamics separation:

  • dyn3d:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • dyn3dpar:
  • adapted gcm.F so that all physics initializations are now done in iniphysiq.
  • updated calfis_p.F to follow up with changes.
  • copied over updated "bands.F90" from LMDZ5.
  • dynphy_lonlat:
  • calfis_p.F90, mod_interface_dyn_phys.F90, follow up of changes in phy_common/mod_* routines
  • phy_common:
  • added "geometry_mod.F90" to store information about the grid (replaces phy*/comgeomphy.F90) and give variables friendlier names: rlond => longitude , rlatd => latitude, airephy => cell_area, cuphy => dx , cvphy => dy
  • added "physics_distribution_mod.F90"
  • updated "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_mpi_data.F90", "mod_phys_lmdz_para.F90", "mod_phys_lmdz_mpi_transfert.F90", "mod_grid_phy_lmdz.F90", "mod_phys_lmdz_omp_data.F90", "mod_phys_lmdz_omp_transfert.F90", "write_field_phy.F90" and "ioipsl_getin_p_mod.F90" to LMDZ5 versions.
  • phy[venus/titan/mars/std]:
  • removed "init_phys_lmdz.F90", "comgeomphy.F90"; adapted routines to use geometry_mod (longitude, latitude, cell_area, etc.)

EM

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