source: trunk/LMDZ.MARS/libf/phymars/initracer.F @ 1226

Last change on this file since 1226 was 1226, checked in by aslmd, 11 years ago

LMDZ.MARS : Replaced comcstfi and planete includes by modules.

File size: 21.4 KB
Line 
1      SUBROUTINE initracer(ngrid,nq,qsurf)
2
3#ifndef MESOSCALE
4       use infotrac, only: tname
5#endif
6       use tracer_mod
7       USE comcstfi_h
8       IMPLICIT NONE
9c=======================================================================
10c   subject:
11c   --------
12c   Initialization related to tracer
13c   (transported dust, water, chemical species, ice...)
14c
15c   Name of the tracer
16c
17c   Test of dimension :
18c   Initialize tracer related data in tracer_mod, using tracer names provided
19c   by the dynamics in "infotrac"
20c
21c
22c   author: F.Forget
23c   ------
24c    Modifs: Franck Montmessin, Sebastien Lebonnois (june 2003)
25c            Ehouarn Millour (oct. 2008) identify tracers by their names
26c=======================================================================
27
28
29!#include "dimensions.h"
30!#include "dimphys.h"
31#include "callkeys.h"
32!#include "tracer.h"
33!#include "advtrac.h"
34!#include "comgeomfi.h"
35
36!#include "surfdat.h"
37
38      integer,intent(in) :: ngrid ! number of atmospheric columns
39      integer,intent(in) :: nq ! number of tracers
40      real,intent(out) :: qsurf(ngrid,nq) ! tracer on surface (e.g.  kg.m-2)
41
42      integer iq,ig,count
43      real r0_lift , reff_lift, nueff_lift
44c     Ratio of small over large dust particles (used when both
45c       doubleq and the submicron mode are active); In Montmessin
46c       et al. (2002), a value of 25 has been deduced;
47      real, parameter :: popratio = 25.
48      character(len=20) :: txt ! to store some text
49
50c-----------------------------------------------------------------------
51c  radius(nq)      ! aerosol particle radius (m)
52c  rho_q(nq)       ! tracer densities (kg.m-3)
53c  alpha_lift(nq)  ! saltation vertical flux/horiz flux ratio (m-1)
54c  alpha_devil(nq) ! lifting coeeficient by dust devil
55c  rho_dust          ! Mars dust density
56c  rho_ice           ! Water ice density
57c  nuice_ref         ! Effective variance nueff of the
58c                    !   water-ice size distributions
59c  doubleq           ! if method with mass (iq=1) and number(iq=2) mixing ratio
60c  varian            ! Characteristic variance of log-normal distribution
61c-----------------------------------------------------------------------
62
63! Initialization: allocate arrays in tracer_mod
64      allocate(mmol(nq))
65      allocate(radius(nq))
66      allocate(rho_q(nq))
67      allocate(alpha_lift(nq))
68      allocate(alpha_devil(nq))
69      allocate(igcm_dustbin(nq))
70      allocate(nqdust(nq))
71
72#ifndef MESOSCALE
73      allocate(noms(nq))
74! Initialization: get tracer names from the dynamics and check if we are
75!                 using 'old' tracer convention ('q01',q02',...)
76!                 or new convention (full tracer names)
77      ! check if tracers have 'old' names
78      count=0
79      do iq=1,nq
80        txt=" "
81        write(txt,'(a1,i2.2)') 'q',iq
82        if (txt.eq.tname(iq)) then
83          count=count+1
84        endif
85      enddo ! of do iq=1,nq
86     
87      if (count.eq.nq) then
88        write(*,*) "initracer: tracers seem to follow old naming ",
89     &             "convention (q01,q02,...)"
90        write(*,*) "you should run newstart to rename them"
91        stop
92      endif
93
94      ! copy tracer names from dynamics
95      do iq=1,nq
96        noms(iq)=tname(iq)
97      enddo
98#endif
99
100c------------------------------------------------------------
101c         NAME and molar mass of the tracer
102c------------------------------------------------------------
103   
104! Identify tracers by their names: (and set corresponding values of mmol)
105      ! 0. initialize tracer indexes to zero:
106      igcm_dustbin(1:nq)=0
107
108      igcm_dust_mass=0
109      igcm_dust_number=0
110      igcm_ccn_mass=0
111      igcm_ccn_number=0
112      igcm_dust_submicron=0
113      igcm_h2o_vap=0
114      igcm_h2o_ice=0
115      igcm_co2=0
116      igcm_co=0
117      igcm_o=0
118      igcm_o1d=0
119      igcm_o2=0
120      igcm_o3=0
121      igcm_h=0
122      igcm_h2=0
123      igcm_oh=0
124      igcm_ho2=0
125      igcm_h2o2=0
126      igcm_ch4=0
127      igcm_n2=0
128      igcm_ar=0
129      igcm_ar_n2=0
130      igcm_n=0
131      igcm_no=0
132      igcm_no2=0
133      igcm_n2d=0
134      igcm_co2plus=0
135      igcm_oplus=0
136      igcm_o2plus=0
137      igcm_coplus=0
138      igcm_cplus=0
139      igcm_nplus=0
140      igcm_noplus=0
141      igcm_n2plus=0
142      igcm_hplus=0
143      igcm_hco2plus=0
144      igcm_elec=0
145
146      ! 1. find dust tracers
147      count=0
148      if (dustbin.gt.0) then
149        do iq=1,nq
150          txt=" "
151          write(txt,'(a4,i2.2)')'dust',count+1
152          if (noms(iq).eq.txt) then
153            count=count+1
154            igcm_dustbin(count)=iq
155            mmol(iq)=100.
156          endif
157        enddo !do iq=1,nq
158      endif ! of if (dustbin.gt.0)
159      if (doubleq) then
160        do iq=1,nq
161          if (noms(iq).eq."dust_mass") then
162            igcm_dust_mass=iq
163            count=count+1
164          endif
165          if (noms(iq).eq."dust_number") then
166            igcm_dust_number=iq
167            count=count+1
168          endif
169        enddo
170      endif ! of if (doubleq)
171      if (microphys) then
172        do iq=1,nq
173          if (noms(iq).eq."ccn_mass") then
174            igcm_ccn_mass=iq
175            count=count+1
176          endif
177          if (noms(iq).eq."ccn_number") then
178            igcm_ccn_number=iq
179            count=count+1
180          endif
181        enddo
182      endif ! of if (microphys)
183      if (submicron) then
184        do iq=1,nq
185          if (noms(iq).eq."dust_submicron") then
186            igcm_dust_submicron=iq
187            mmol(iq)=100.
188            count=count+1
189          endif
190        enddo
191      endif ! of if (submicron)
192      ! 2. find chemistry and water tracers
193      do iq=1,nq
194        if (noms(iq).eq."co2") then
195          igcm_co2=iq
196          mmol(igcm_co2)=44.
197          count=count+1
198        endif
199        if (noms(iq).eq."co") then
200          igcm_co=iq
201          mmol(igcm_co)=28.
202          count=count+1
203        endif
204        if (noms(iq).eq."o") then
205          igcm_o=iq
206          mmol(igcm_o)=16.
207          count=count+1
208        endif
209        if (noms(iq).eq."o1d") then
210          igcm_o1d=iq
211          mmol(igcm_o1d)=16.
212          count=count+1
213        endif
214        if (noms(iq).eq."o2") then
215          igcm_o2=iq
216          mmol(igcm_o2)=32.
217          count=count+1
218        endif
219        if (noms(iq).eq."o3") then
220          igcm_o3=iq
221          mmol(igcm_o3)=48.
222          count=count+1
223        endif
224        if (noms(iq).eq."h") then
225          igcm_h=iq
226          mmol(igcm_h)=1.
227          count=count+1
228        endif
229        if (noms(iq).eq."h2") then
230          igcm_h2=iq
231          mmol(igcm_h2)=2.
232          count=count+1
233        endif
234        if (noms(iq).eq."oh") then
235          igcm_oh=iq
236          mmol(igcm_oh)=17.
237          count=count+1
238        endif
239        if (noms(iq).eq."ho2") then
240          igcm_ho2=iq
241          mmol(igcm_ho2)=33.
242          count=count+1
243        endif
244        if (noms(iq).eq."h2o2") then
245          igcm_h2o2=iq
246          mmol(igcm_h2o2)=34.
247          count=count+1
248        endif
249        if (noms(iq).eq."n2") then
250          igcm_n2=iq
251          mmol(igcm_n2)=28.
252          count=count+1
253        endif
254        if (noms(iq).eq."ch4") then
255          igcm_ch4=iq
256          mmol(igcm_ch4)=16.
257          count=count+1
258        endif
259        if (noms(iq).eq."ar") then
260          igcm_ar=iq
261          mmol(igcm_ar)=40.
262          count=count+1
263        endif
264        if (noms(iq).eq."n") then
265          igcm_n=iq
266          mmol(igcm_n)=14.
267          count=count+1
268        endif
269        if (noms(iq).eq."no") then
270          igcm_no=iq
271          mmol(igcm_no)=30.
272          count=count+1
273        endif
274        if (noms(iq).eq."no2") then
275          igcm_no2=iq
276          mmol(igcm_no2)=46.
277          count=count+1
278        endif
279        if (noms(iq).eq."n2d") then
280          igcm_n2d=iq
281          mmol(igcm_n2d)=28.
282          count=count+1
283        endif
284        if (noms(iq).eq."co2plus") then
285          igcm_co2plus=iq
286          mmol(igcm_co2plus)=44.
287          count=count+1
288        endif
289        if (noms(iq).eq."oplus") then
290          igcm_oplus=iq
291          mmol(igcm_oplus)=16.
292          count=count+1
293        endif
294        if (noms(iq).eq."o2plus") then
295          igcm_o2plus=iq
296          mmol(igcm_o2plus)=32.
297          count=count+1
298        endif
299        if (noms(iq).eq."coplus") then
300          igcm_coplus=iq
301          mmol(igcm_coplus)=28.
302          count=count+1
303        endif
304        if (noms(iq).eq."cplus") then
305          igcm_cplus=iq
306          mmol(igcm_cplus)=12.
307          count=count+1
308        endif
309        if (noms(iq).eq."nplus") then
310          igcm_nplus=iq
311          mmol(igcm_nplus)=14.
312          count=count+1
313        endif
314        if (noms(iq).eq."noplus") then
315          igcm_noplus=iq
316          mmol(igcm_noplus)=30.
317          count=count+1
318        endif
319        if (noms(iq).eq."n2plus") then
320          igcm_n2plus=iq
321          mmol(igcm_n2plus)=28.
322          count=count+1
323        endif
324        if (noms(iq).eq."hplus") then
325          igcm_hplus=iq
326          mmol(igcm_hplus)=1.
327          count=count+1
328        endif
329        if (noms(iq).eq."hco2plus") then
330          igcm_hco2plus=iq
331          mmol(igcm_hco2plus)=45.
332          count=count+1
333        endif
334        if (noms(iq).eq."elec") then
335          igcm_elec=iq
336          mmol(igcm_elec)=1./1822.89
337          count=count+1
338        endif
339        if (noms(iq).eq."h2o_vap") then
340          igcm_h2o_vap=iq
341          mmol(igcm_h2o_vap)=18.
342          count=count+1
343        endif
344        if (noms(iq).eq."h2o_ice") then
345          igcm_h2o_ice=iq
346          mmol(igcm_h2o_ice)=18.
347          count=count+1
348        endif
349        ! Other stuff: e.g. for simulations using co2 + neutral gaz
350        if (noms(iq).eq."Ar_N2") then
351          igcm_ar_n2=iq
352          mmol(igcm_ar_n2)=30.
353          count=count+1
354        endif
355
356      enddo ! of do iq=1,nq
357     
358      ! check that we identified all tracers:
359      if (count.ne.nq) then
360        write(*,*) "initracer: found only ",count," tracers"
361        write(*,*) "               expected ",nq
362        do iq=1,count
363          write(*,*)'      ',iq,' ',trim(noms(iq))
364        enddo
365        stop
366      else
367        write(*,*) "initracer: found all expected tracers, namely:"
368        do iq=1,nq
369          write(*,*)'      ',iq,' ',trim(noms(iq))
370        enddo
371      endif
372
373      ! if water cycle but iceparty=.false., there will nevertheless be
374      ! water ice at the surface (iceparty is not used anymore, but this
375      ! part is still relevant, as we want to stay compatible with the
376      ! older versions).
377      if (water.and.(igcm_h2o_ice.eq.0)) then
378        igcm_h2o_ice=igcm_h2o_vap ! so that qsurf(i_h2o_ice) is identified
379                                  ! even though there is no q(i_h2o_ice)
380      else
381       ! surface ice qsurf(i_h2o_ice) was loaded twice by phyetat0,
382       ! as qsurf(i_h2o_vap) & as qsurf(i_h2o_ice), so to be clean:
383       if (igcm_h2o_vap.ne.0) then
384         qsurf(1:ngrid,igcm_h2o_vap)=0
385       endif
386      endif
387
388c------------------------------------------------------------
389c     Initialize tracers .... (in tracer_mod)
390c------------------------------------------------------------
391      ! start by setting everything to (default) zero
392      rho_q(1:nq)=0     ! tracer density (kg.m-3)
393      radius(1:nq)=0.   ! tracer particle radius (m)
394      alpha_lift(1:nq) =0.  ! tracer saltation vertical flux/horiz flux ratio (m-1)
395      alpha_devil(1:nq)=0.  ! tracer lifting coefficient by dust devils
396
397
398      ! some reference values
399      rho_dust=2500.  ! Mars dust density (kg.m-3)
400      rho_ice=920.    ! Water ice density (kg.m-3)
401      nuice_ref=0.1   ! Effective variance nueff of the
402                      ! water-ice size distribution
403      !!!nuice_sed=0.45   ! Sedimentation effective variance
404                      ! of the water-ice size distribution
405
406      if (doubleq) then
407c       "doubleq" technique
408c       -------------------
409c      (transport of mass and number mixing ratio)
410c       iq=1: Q mass mixing ratio, iq=2: N number mixing ratio
411
412        if( (nq.lt.2).or.(water.and.(nq.lt.4)) ) then
413          write(*,*)'initracer: nq is too low : nq=', nq
414          write(*,*)'water= ',water,' doubleq= ',doubleq   
415        end if
416
417        nueff_lift = 0.5
418        varian=sqrt(log(1.+nueff_lift))
419
420        rho_q(igcm_dust_mass)=rho_dust
421        rho_q(igcm_dust_number)=rho_dust
422
423c       Intermediate calcul for computing geometric mean radius r0
424c       as a function of mass and number mixing ratio Q and N
425c       (r0 = (r3n_q * Q/ N)^(1/3))
426        r3n_q = exp(-4.5*varian**2)*(3./4.)/(pi*rho_dust)
427
428c       Intermediate calcul for computing effective radius reff
429c       from geometric mean radius r0
430c       (reff = ref_r0 * r0)
431        ref_r0 = exp(2.5*varian**2)
432       
433c       lifted dust :
434c       '''''''''''
435        reff_lift = 3.0e-6 !3.e-6 !Effective radius of lifted dust (m)
436        alpha_devil(igcm_dust_mass)=9.e-9   !  dust devil lift mass coeff
437c       alpha_lift(igcm_dust_mass)=3.0e-15  !  Lifted mass coeff
438        alpha_lift(igcm_dust_mass)=1.e-6 !1.e-6 !Lifted mass coeff
439
440        r0_lift = reff_lift/ref_r0
441        alpha_devil(igcm_dust_number)=r3n_q*
442     &                        alpha_devil(igcm_dust_mass)/r0_lift**3
443        alpha_lift(igcm_dust_number)=r3n_q*
444     &                        alpha_lift(igcm_dust_mass)/r0_lift**3
445
446        radius(igcm_dust_mass) = reff_lift
447        radius(igcm_dust_number) = reff_lift
448
449        write(*,*) "initracer: doubleq_param reff_lift:", reff_lift
450        write(*,*) "initracer: doubleq_param nueff_lift:", nueff_lift
451        write(*,*) "initracer: doubleq_param alpha_lift:",
452     &    alpha_lift(igcm_dust_mass)
453      else
454
455       ! initialize varian, which may be used (e.g. by surfacearea)
456       ! even with conrath dust
457       nueff_lift = 0.5
458       varian=sqrt(log(1.+nueff_lift))
459
460       if (dustbin.gt.1) then
461        print*,'initracer: STOP!',
462     $   ' properties of dust need to be set in initracer !!!'
463        stop
464
465       else if (dustbin.eq.1) then
466
467c       This will be used for 1 dust particle size:
468c       ------------------------------------------
469        radius(igcm_dustbin(1))=3.e-6
470        alpha_lift(igcm_dustbin(1))=0.0e-6
471        alpha_devil(igcm_dustbin(1))=7.65e-9
472        rho_q(igcm_dustbin(1))=rho_dust
473
474       endif
475      end if    ! (doubleq)
476
477
478c     Scavenging of dust particles by H2O clouds:
479c     ------------------------------------------
480c     Initialize the two tracers used for the CCNs
481      if (water.AND.doubleq.AND.scavenging) then
482        radius(igcm_ccn_mass) = radius(igcm_dust_mass)
483        alpha_lift(igcm_ccn_mass) = 1e-30
484        alpha_devil(igcm_ccn_mass) = 1e-30
485        rho_q(igcm_ccn_mass) = rho_dust
486
487        radius(igcm_ccn_number) = radius(igcm_ccn_mass)
488        alpha_lift(igcm_ccn_number) = alpha_lift(igcm_ccn_mass)
489        alpha_devil(igcm_ccn_number) = alpha_devil(igcm_ccn_mass)
490        rho_q(igcm_ccn_number) = rho_q(igcm_ccn_mass)
491      endif ! of if (water.AND.doubleq.AND.scavenging)
492
493c     Submicron dust mode:
494c     --------------------
495
496      if (submicron) then
497        radius(igcm_dust_submicron)=0.1e-6
498        rho_q(igcm_dust_submicron)=rho_dust
499        if (doubleq) then
500c         If doubleq is also active, we use the population ratio:
501          alpha_lift(igcm_dust_submicron) =
502     &      alpha_lift(igcm_dust_number)*popratio*
503     &      rho_q(igcm_dust_submicron)*4./3.*pi*
504     &      radius(igcm_dust_submicron)**3.
505          alpha_devil(igcm_dust_submicron)=1.e-30
506        else
507          alpha_lift(igcm_dust_submicron)=1e-6
508          alpha_devil(igcm_dust_submicron)=1.e-30
509        endif ! (doubleq)
510      end if  ! (submicron)
511
512c     Initialization for water vapor
513c     ------------------------------
514      if(water) then
515         radius(igcm_h2o_vap)=0.
516         alpha_lift(igcm_h2o_vap) =0.
517         alpha_devil(igcm_h2o_vap)=0.
518         if(water.and.(nq.ge.2)) then
519           radius(igcm_h2o_ice)=3.e-6
520           rho_q(igcm_h2o_ice)=rho_ice
521           alpha_lift(igcm_h2o_ice) =0.
522           alpha_devil(igcm_h2o_ice)=0.
523         elseif(water.and.(nq.lt.2)) then
524            write(*,*) 'nq is too low : nq=', nq
525            write(*,*) 'water= ',water
526         endif
527
528      end if  ! (water)
529
530c     Output for records:
531c     ~~~~~~~~~~~~~~~~~~
532      write(*,*)
533      Write(*,*) '******** initracer : dust transport parameters :'
534      write(*,*) 'alpha_lift = ', alpha_lift
535      write(*,*) 'alpha_devil = ', alpha_devil
536      write(*,*) 'radius  = ', radius
537      if(doubleq) then
538        write(*,*) 'reff_lift (um) =  ', reff_lift
539        write(*,*) 'size distribution variance  = ', varian
540        write(*,*) 'r3n_q , ref_r0 : ', r3n_q , ref_r0
541      end if
542
543!
544!     some extra (possibly redundant) sanity checks for tracers:
545!     ---------------------------------------------------------
546
547       if (doubleq) then
548       ! verify that we indeed have dust_mass and dust_number tracers
549         if (igcm_dust_mass.eq.0) then
550           write(*,*) "initracer: error !!"
551           write(*,*) "  cannot use doubleq option without ",
552     &                "a dust_mass tracer !"
553           stop
554         endif
555         if (igcm_dust_number.eq.0) then
556           write(*,*) "initracer: error !!"
557           write(*,*) "  cannot use doubleq option without ",
558     &                "a dust_number tracer !"
559           stop
560         endif
561       endif
562
563       if ((.not.doubleq).and.(dustbin.gt.0)) then
564       ! verify that we indeed have 'dustbin' dust tracers
565         count=0
566         do iq=1,dustbin
567           if (igcm_dustbin(iq).ne.0) then
568             count=count+1
569           endif
570         enddo
571         if (count.ne.dustbin) then
572           write(*,*) "initracer: error !!"
573           write(*,*) "  dusbin is set to ",dustbin,
574     &                " but we only have the following dust tracers:"
575           do iq=1,count
576             write(*,*)"   ",trim(noms(igcm_dustbin(iq)))
577           enddo
578           stop
579         endif
580       endif
581
582       if (water) then
583       ! verify that we indeed have h2o_vap and h2o_ice tracers
584         if (igcm_h2o_vap.eq.0) then
585           write(*,*) "initracer: error !!"
586           write(*,*) "  cannot use water option without ",
587     &                "an h2o_vap tracer !"
588           stop
589         endif
590         if (igcm_h2o_ice.eq.0) then
591           write(*,*) "initracer: error !!"
592           write(*,*) "  cannot use water option without ",
593     &                "an h2o_ice tracer !"
594           stop
595         endif
596       endif
597
598       if (scavenging) then
599       ! verify that we indeed have ccn_mass and ccn_number tracers
600         if (igcm_ccn_mass.eq.0) then
601           write(*,*) "initracer: error !!"
602           write(*,*) "  cannot use scavenging option without ",
603     &                "a ccn_mass tracer !"
604           stop
605         endif
606         if (igcm_ccn_number.eq.0) then
607           write(*,*) "initracer: error !!"
608           write(*,*) "  cannot use scavenging option without ",
609     &                "a ccn_number tracer !"
610           stop
611         endif
612       endif ! of if (scavenging)
613
614       if (photochem .or. callthermos) then
615       ! verify that we indeed have the chemistry tracers
616         if (igcm_co2.eq.0) then
617           write(*,*) "initracer: error !!"
618           write(*,*) "  cannot use chemistry option without ",
619     &                "a co2 tracer !"
620         stop
621         endif
622         if (igcm_co.eq.0) then
623           write(*,*) "initracer: error !!"
624           write(*,*) "  cannot use chemistry option without ",
625     &                "a co tracer !"
626         stop
627         endif
628         if (igcm_o.eq.0) then
629           write(*,*) "initracer: error !!"
630           write(*,*) "  cannot use chemistry option without ",
631     &                "a o tracer !"
632         stop
633         endif
634         if (igcm_o1d.eq.0) then
635           write(*,*) "initracer: error !!"
636           write(*,*) "  cannot use chemistry option without ",
637     &                "a o1d tracer !"
638         stop
639         endif
640         if (igcm_o2.eq.0) then
641           write(*,*) "initracer: error !!"
642           write(*,*) "  cannot use chemistry option without ",
643     &                "an o2 tracer !"
644         stop
645         endif
646         if (igcm_o3.eq.0) then
647           write(*,*) "initracer: error !!"
648           write(*,*) "  cannot use chemistry option without ",
649     &                "an o3 tracer !"
650         stop
651         endif
652         if (igcm_h.eq.0) then
653           write(*,*) "initracer: error !!"
654           write(*,*) "  cannot use chemistry option without ",
655     &                "a h tracer !"
656         stop
657         endif
658         if (igcm_h2.eq.0) then
659           write(*,*) "initracer: error !!"
660           write(*,*) "  cannot use chemistry option without ",
661     &                "a h2 tracer !"
662         stop
663         endif
664         if (igcm_oh.eq.0) then
665           write(*,*) "initracer: error !!"
666           write(*,*) "  cannot use chemistry option without ",
667     &                "an oh tracer !"
668         stop
669         endif
670         if (igcm_ho2.eq.0) then
671           write(*,*) "initracer: error !!"
672           write(*,*) "  cannot use chemistry option without ",
673     &                "a ho2 tracer !"
674         stop
675         endif
676         if (igcm_h2o2.eq.0) then
677           write(*,*) "initracer: error !!"
678           write(*,*) "  cannot use chemistry option without ",
679     &                "a h2o2 tracer !"
680         stop
681         endif
682         if (igcm_n2.eq.0) then
683           write(*,*) "initracer: error !!"
684           write(*,*) "  cannot use chemistry option without ",
685     &                "a n2 tracer !"
686         stop
687         endif
688         if (igcm_ar.eq.0) then
689           write(*,*) "initracer: error !!"
690           write(*,*) "  cannot use chemistry option without ",
691     &                "an ar tracer !"
692         stop
693         endif
694       endif ! of if (photochem .or. callthermos)
695
696      end
Note: See TracBrowser for help on using the repository browser.