source: trunk/LMDZ.GENERIC/libf/phystd/tabfi.F @ 1626

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

All GCMS:
More updates to enforce dynamics/physics separation:

get rid of references to "temps_mod" from physics packages;
make a "time_phylmdz_mod.F90" module to store that
information and fill it via "iniphysiq".

EM

File size: 20.3 KB
Line 
1c=======================================================================
2      SUBROUTINE tabfi(ngrid,nid,Lmodif,tab0,day_ini,lmax,p_rad,
3     .                 p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time)
4c=======================================================================
5c
6c   C. Hourdin 15/11/96
7c
8c   Object:        Lecture du tab_cntrl physique dans un fichier
9c   ------            et initialisation des constantes physiques
10c
11c   Arguments:
12c   ----------
13c
14c     Inputs:
15c     ------
16c
17c      - nid:    unitne logique du fichier ou on va lire le tab_cntrl   
18c                      (ouvert dans le programme appellant)
19c
20c                 si nid=0:
21c                       pas de lecture du tab_cntrl mais
22c                       Valeurs par default des constantes physiques
23c       
24c      - tab0:    Offset de tab_cntrl a partir duquel sont ranges
25c                  les parametres physiques (50 pour start_archive)
26c
27c      - Lmodif:  si on souhaite modifier les constantes  Lmodif = 1 = TRUE
28c
29c
30c     Outputs:
31c     --------
32c
33c      - day_ini: tab_cntrl(tab0+3) (Dans les cas ou l'on souhaite
34c                              comparer avec le day_ini dynamique)
35c
36c      - lmax:    tab_cntrl(tab0+2) (pour test avec nlayer)
37c
38c      - p_rad
39c      - p_omeg   !
40c      - p_g      ! Constantes physiques ayant des
41c      - p_mugaz  ! homonymes dynamiques
42c      - p_daysec !
43c
44c=======================================================================
45! to use  'getin'
46      use ioipsl_getincom , only: getin
47
48      use surfdat_h, only: emisice, iceradius, dtemisice,
49     &                     emissiv
50      use comsoil_h, only: volcapa
51      use iostart, only: get_var
52      use mod_phys_lmdz_para, only: is_parallel
53      use planete_mod, only: year_day, periastr, apoastr, peri_day,
54     &                       obliquit, z0, lmixmin, emin_turb
55      use comcstfi_mod, only: rad, omeg, g, mugaz, rcp, cpp, r
56      use time_phylmdz_mod, only: dtphys, daysec
57      use callkeys_mod, only: check_cpp_match,force_cpp
58      implicit none
59 
60#include "netcdf.inc"
61
62c-----------------------------------------------------------------------
63c   Declarations
64c-----------------------------------------------------------------------
65
66c Arguments
67c ---------
68      INTEGER,INTENT(IN) :: ngrid,nid,tab0
69      INTEGER*4,INTENT(OUT) :: day_ini
70      INTEGER,INTENT(IN) :: Lmodif
71      INTEGER,INTENT(OUT) :: lmax
72      REAL,INTENT(OUT) :: p_rad,p_omeg,p_g,p_cpp,p_mugaz,p_daysec,time
73
74c Variables
75c ---------
76      INTEGER,PARAMETER :: length=100
77      REAL tab_cntrl(length) ! array in which are stored the run's parameters
78      INTEGER  ierr,nvarid
79      INTEGER size
80      CHARACTER modif*20
81      LOGICAL :: found
82     
83      write(*,*)"tabfi: nid=",nid," tab0=",tab0," Lmodif=",Lmodif
84
85      IF (nid.eq.0) then
86c-----------------------------------------------------------------------
87c  Initialization of various physical constants to defaut values (nid = 0 case)
88c-----------------------------------------------------------------------
89      ELSE
90c-----------------------------------------------------------------------
91c  Initialization of physical constants by reading array tab_cntrl(:)
92c               which contains these parameters (nid != 0 case)
93c-----------------------------------------------------------------------
94c Read 'controle' array
95c
96
97       call get_var("controle",tab_cntrl,found)
98       if (.not.found) then
99         write(*,*)"tabfi: Failed reading <controle> array"
100         call abort
101       else
102         write(*,*)'tabfi: tab_cntrl',tab_cntrl
103       endif
104c
105c  Initialization of some physical constants
106c informations on physics grid
107!      if(ngrid.ne.tab_cntrl(tab0+1)) then
108!         print*,'tabfi: WARNING !!! tab_cntrl(tab0+1).ne.ngrid'
109!         print*,tab_cntrl(tab0+1),ngrid
110!      endif
111      lmax = nint(tab_cntrl(tab0+2))
112      day_ini = tab_cntrl(tab0+3)
113      time = tab_cntrl(tab0+4)
114      write (*,*) 'IN tabfi day_ini=',day_ini
115c Informations about planet for dynamics and physics
116      rad = tab_cntrl(tab0+5)
117      omeg = tab_cntrl(tab0+6)
118      g = tab_cntrl(tab0+7)
119      mugaz = tab_cntrl(tab0+8)
120      rcp = tab_cntrl(tab0+9)
121      cpp=(8.314511/(mugaz/1000.0))/rcp
122      daysec = tab_cntrl(tab0+10)
123      dtphys = tab_cntrl(tab0+11)
124c Informations about planet for the physics only
125      year_day = tab_cntrl(tab0+14)
126      periastr = tab_cntrl(tab0+15)
127      apoastr = tab_cntrl(tab0+16)
128      peri_day = tab_cntrl(tab0+17)
129      obliquit = tab_cntrl(tab0+18)
130c boundary layer and turbeulence
131      z0 = tab_cntrl(tab0+19)
132      lmixmin = tab_cntrl(tab0+20)
133      emin_turb = tab_cntrl(tab0+21)
134c optical properties of polar caps and ground emissivity
135      emisice(1) = tab_cntrl(tab0+24)
136      emisice(2) = tab_cntrl(tab0+25)
137      emissiv    = tab_cntrl(tab0+26)
138      iceradius(1)= tab_cntrl(tab0+31) ! mean scat radius of CO2 snow (north)
139      iceradius(2)= tab_cntrl(tab0+32) ! mean scat radius of CO2 snow (south)
140      dtemisice(1)= tab_cntrl(tab0+33) !time scale for snow metamorphism (north)
141      dtemisice(2)= tab_cntrl(tab0+34) !time scale for snow metamorphism (south)
142c soil properties
143      volcapa = tab_cntrl(tab0+35) ! volumetric heat capacity
144c-----------------------------------------------------------------------
145c       Save some constants for later use (as routine arguments)
146c-----------------------------------------------------------------------
147      p_omeg = omeg
148      p_g = g
149      p_cpp = cpp
150      p_mugaz = mugaz
151      p_daysec = daysec
152      p_rad=rad
153
154      ENDIF    ! end of (nid = 0)
155
156c-----------------------------------------------------------------------
157c       Write physical constants to output before modifying them
158c-----------------------------------------------------------------------
159 
160   6  FORMAT(a20,e15.6,e15.6)
161   5  FORMAT(a20,f12.2,f12.2)
162 
163      write(*,*) '*****************************************************'
164      write(*,*) 'Reading tab_cntrl when calling tabfi before changes'
165      write(*,*) '*****************************************************'
166      write(*,5) '(1)        = ngrid?',tab_cntrl(tab0+1),float(ngrid)
167      write(*,5) '(2)            lmax',tab_cntrl(tab0+2),float(lmax)
168      write(*,5) '(3)         day_ini',tab_cntrl(tab0+3),float(day_ini)
169      write(*,5) '(5)             rad',tab_cntrl(tab0+5),rad
170      write(*,5) '(10)         daysec',tab_cntrl(tab0+10),daysec
171      write(*,6) '(6)            omeg',tab_cntrl(tab0+6),omeg
172      write(*,5) '(7)               g',tab_cntrl(tab0+7),g
173      write(*,5) '(8)           mugaz',tab_cntrl(tab0+8),mugaz
174      write(*,5) '(9)             rcp',tab_cntrl(tab0+9),rcp
175      write(*,6) '(11)        dtphys?',tab_cntrl(tab0+11),dtphys
176
177      write(*,5) '(14)       year_day',tab_cntrl(tab0+14),year_day
178      write(*,5) '(15)       periastr',tab_cntrl(tab0+15),periastr
179      write(*,5) '(16)        apoastr',tab_cntrl(tab0+16),apoastr
180      write(*,5) '(17)       peri_day',tab_cntrl(tab0+17),peri_day
181      write(*,5) '(18)       obliquit',tab_cntrl(tab0+18),obliquit
182
183      write(*,6) '(19)             z0',tab_cntrl(tab0+19),z0
184      write(*,6) '(21)      emin_turb',tab_cntrl(tab0+21),emin_turb
185      write(*,5) '(20)        lmixmin',tab_cntrl(tab0+20),lmixmin
186
187      write(*,5) '(26)        emissiv',tab_cntrl(tab0+26),emissiv
188      write(*,5) '(24)     emisice(1)',tab_cntrl(tab0+24),emisice(1)
189      write(*,5) '(25)     emisice(2)',tab_cntrl(tab0+25),emisice(2)
190      write(*,6) '(31)   iceradius(1)',tab_cntrl(tab0+31),iceradius(1)
191      write(*,6) '(32)   iceradius(2)',tab_cntrl(tab0+32),iceradius(2)
192      write(*,5) '(33)   dtemisice(1)',tab_cntrl(tab0+33),dtemisice(1)
193      write(*,5) '(34)   dtemisice(2)',tab_cntrl(tab0+34),dtemisice(2)
194
195      write(*,5) '(35)        volcapa',tab_cntrl(tab0+35),volcapa
196
197      write(*,*)
198      write(*,*) 'Lmodif in tabfi!!!!!!!',Lmodif
199
200c-----------------------------------------------------------------------
201c        Modifications...
202! NB: Modifying controls should only be done by newstart, and in seq mode
203      if ((Lmodif.eq.1).and.is_parallel) then
204        write(*,*) "tabfi: Error modifying tab_control should",
205     &             " only happen in serial mode (eg: by newstart)"
206        stop
207      endif
208c-----------------------------------------------------------------------
209
210      IF(Lmodif.eq.1) then
211
212      write(*,*)
213      write(*,*) 'Change values in tab_cntrl ? :'
214      write(*,*) '~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~'
215      write(*,*) '(Current values given above)'
216      write(*,*)
217      write(*,*) '(3)          day_ini : Initial day (=0 at Ls=0)'
218      write(*,*) '(19)              z0 :  surface roughness (m)'
219      write(*,*) '(21)       emin_turb :  minimal energy (PBL)'
220      write(*,*) '(20)         lmixmin : mixing length (PBL)'
221      write(*,*) '(26)         emissiv : ground emissivity'
222      write(*,*) '(24 et 25)   emisice : CO2 ice max emissivity '
223      write(*,*) '(31 et 32) iceradius : mean scat radius of CO2 snow'
224      write(*,*) '(33 et 34) dtemisice : time scale for snow',
225     &           'metamorphism'
226      write(*,*) '(35)      volcapa : soil volumetric heat capacity'
227      write(*,*) '(18)     obliquit : planet obliquity (deg)'
228      write(*,*) '(17)     peri_day : periastron date (sols since Ls=0)'
229      write(*,*) '(15)     periastr : min. star-planet dist (UA)'
230      write(*,*) '(16)     apoastr  : max. star-planet (UA)'
231      write(*,*) '(14)     year_day : length of year (in sols)'
232      write(*,*) '(5)      rad      : radius of the planet (m)'
233      write(*,*) '(6)      omeg     : planet rotation rate (rad/s)'
234      write(*,*) '(7)      g        : gravity (m/s2)'
235      write(*,*) '(8)      mugaz    : molecular mass '
236      write(*,*) '                       of the atmosphere (g/mol)'
237      write(*,*) '(9)      rcp      : r/Cp'
238      write(*,*) '(8)+(9)  calc_cpp_mugaz : r/Cp and mugaz '
239      write(*,*) '                 computed from gases.def'
240      write(*,*) '(10)     daysec   : length of a sol (s)'
241      write(*,*)
242 
243 
244      do while(modif(1:1).ne.'hello')
245        write(*,*)
246        write(*,*)
247        write(*,*) 'Changes to perform ?'
248        write(*,*) '   (enter keyword or return )'
249        write(*,*)
250        read(*,fmt='(a20)') modif
251        if (modif(1:1) .eq. ' ') goto 999
252 
253        write(*,*)
254        write(*,*) modif(1:len_trim(modif)) , ' : '
255
256        if (modif(1:len_trim(modif)) .eq. 'day_ini') then
257          write(*,*) 'current value:',day_ini
258          write(*,*) 'enter new value:'
259 101      read(*,*,iostat=ierr) day_ini
260          if(ierr.ne.0) goto 101
261          write(*,*) ' '
262          write(*,*) 'day_ini (new value):',day_ini
263
264        else if (modif(1:len_trim(modif)) .eq. 'z0') then
265          write(*,*) 'current value:',z0
266          write(*,*) 'enter new value:'
267 102      read(*,*,iostat=ierr) z0
268          if(ierr.ne.0) goto 102
269          write(*,*) ' '
270          write(*,*) ' z0 (new value):',z0
271
272        else if (modif(1:len_trim(modif)) .eq. 'emin_turb') then
273          write(*,*) 'current value:',emin_turb
274          write(*,*) 'enter new value:'
275 103      read(*,*,iostat=ierr) emin_turb
276          if(ierr.ne.0) goto 103
277          write(*,*) ' '
278          write(*,*) ' emin_turb (new value):',emin_turb
279
280        else if (modif(1:len_trim(modif)) .eq. 'lmixmin') then
281          write(*,*) 'current value:',lmixmin
282          write(*,*) 'enter new value:'
283 104      read(*,*,iostat=ierr) lmixmin
284          if(ierr.ne.0) goto 104
285          write(*,*) ' '
286          write(*,*) ' lmixmin (new value):',lmixmin
287
288        else if (modif(1:len_trim(modif)) .eq. 'emissiv') then
289          write(*,*) 'current value:',emissiv
290          write(*,*) 'enter new value:'
291 105      read(*,*,iostat=ierr) emissiv
292          if(ierr.ne.0) goto 105
293          write(*,*) ' '
294          write(*,*) ' emissiv (new value):',emissiv
295
296        else if (modif(1:len_trim(modif)) .eq. 'emisice') then
297          write(*,*) 'current value emisice(1) North:',emisice(1)
298          write(*,*) 'enter new value:'
299 106      read(*,*,iostat=ierr) emisice(1)
300          if(ierr.ne.0) goto 106
301          write(*,*)
302          write(*,*) ' emisice(1) (new value):',emisice(1)
303          write(*,*)
304
305          write(*,*) 'current value emisice(2) South:',emisice(2)
306          write(*,*) 'enter new value:'
307 107      read(*,*,iostat=ierr) emisice(2)
308          if(ierr.ne.0) goto 107
309          write(*,*)
310          write(*,*) ' emisice(2) (new value):',emisice(2)
311
312        else if (modif(1:len_trim(modif)) .eq. 'iceradius') then
313          write(*,*) 'current value iceradius(1) North:',iceradius(1)
314          write(*,*) 'enter new value:'
315 110      read(*,*,iostat=ierr) iceradius(1)
316          if(ierr.ne.0) goto 110
317          write(*,*)
318          write(*,*) ' iceradius(1) (new value):',iceradius(1)
319          write(*,*)
320
321          write(*,*) 'current value iceradius(2) South:',iceradius(2)
322          write(*,*) 'enter new value:'
323 111      read(*,*,iostat=ierr) iceradius(2)
324          if(ierr.ne.0) goto 111
325          write(*,*)
326          write(*,*) ' iceradius(2) (new value):',iceradius(2)
327
328        else if (modif(1:len_trim(modif)) .eq. 'dtemisice') then
329          write(*,*) 'current value dtemisice(1) North:',dtemisice(1)
330          write(*,*) 'enter new value:'
331 112      read(*,*,iostat=ierr) dtemisice(1)
332          if(ierr.ne.0) goto 112
333          write(*,*)
334          write(*,*) ' dtemisice(1) (new value):',dtemisice(1)
335          write(*,*)
336
337          write(*,*) 'current value dtemisice(2) South:',dtemisice(2)
338          write(*,*) 'enter new value:'
339 113      read(*,*,iostat=ierr) dtemisice(2)
340          if(ierr.ne.0) goto 113
341          write(*,*)
342          write(*,*) ' dtemisice(2) (new value):',dtemisice(2)
343
344        else if (modif(1:len_trim(modif)) .eq. 'obliquit') then
345          write(*,*) 'current value:',obliquit
346          write(*,*) 'obliquit should be 25.19 on current Mars'
347          write(*,*) 'enter new value:'
348 115      read(*,*,iostat=ierr) obliquit
349          if(ierr.ne.0) goto 115
350          write(*,*)
351          write(*,*) ' obliquit (new value):',obliquit
352
353        else if (modif(1:len_trim(modif)) .eq. 'peri_day') then
354          write(*,*) 'current value:',peri_day
355          write(*,*) 'peri_day should be 485 on current Mars'
356          write(*,*) 'enter new value:'
357 116      read(*,*,iostat=ierr) peri_day
358          if(ierr.ne.0) goto 116
359          write(*,*)
360          write(*,*) ' peri_day (new value):',peri_day
361
362        else if (modif(1:len_trim(modif)) .eq. 'periastr') then
363          write(*,*) 'current value:',periastr
364          write(*,*) 'periastr should be 206.66 on present-day Mars'
365          write(*,*) 'enter new value:'
366 117      read(*,*,iostat=ierr) periastr
367          if(ierr.ne.0) goto 117
368          write(*,*)
369          write(*,*) ' periastr (new value):',periastr
370 
371        else if (modif(1:len_trim(modif)) .eq. 'apoastr') then
372          write(*,*) 'current value:',apoastr
373          write(*,*) 'apoastr should be 249.22 on present-day Mars'
374          write(*,*) 'enter new value:'
375 118      read(*,*,iostat=ierr) apoastr
376          if(ierr.ne.0) goto 118
377          write(*,*)
378          write(*,*) ' apoastr (new value):',apoastr
379 
380        else if (modif(1:len_trim(modif)) .eq. 'volcapa') then
381          write(*,*) 'current value:',volcapa
382          write(*,*) 'enter new value:'
383 119      read(*,*,iostat=ierr) volcapa
384          if(ierr.ne.0) goto 119
385          write(*,*)
386          write(*,*) ' volcapa (new value):',volcapa
387       
388        else if (modif(1:len_trim(modif)).eq.'rad') then
389          write(*,*) 'current value:',rad
390          write(*,*) 'enter new value:'
391 120      read(*,*,iostat=ierr) rad
392          if(ierr.ne.0) goto 120
393          write(*,*)
394          write(*,*) ' rad (new value):',rad
395
396        else if (modif(1:len_trim(modif)).eq.'omeg') then
397          write(*,*) 'current value:',omeg
398          write(*,*) 'enter new value:'
399 121      read(*,*,iostat=ierr) omeg
400          if(ierr.ne.0) goto 121
401          write(*,*)
402          write(*,*) ' omeg (new value):',omeg
403       
404        else if (modif(1:len_trim(modif)).eq.'g') then
405          write(*,*) 'current value:',g
406          write(*,*) 'enter new value:'
407 122      read(*,*,iostat=ierr) g
408          if(ierr.ne.0) goto 122
409          write(*,*)
410          write(*,*) ' g (new value):',g
411
412        else if (modif(1:len_trim(modif)).eq.'mugaz') then
413          write(*,*) 'current value:',mugaz
414          write(*,*) 'enter new value:'
415 123      read(*,*,iostat=ierr) mugaz
416          if(ierr.ne.0) goto 123
417          write(*,*)
418          write(*,*) ' mugaz (new value):',mugaz
419          r=8.314511/(mugaz/1000.0)
420          write(*,*) ' R (new value):',r
421
422        else if (modif(1:len_trim(modif)).eq.'rcp') then
423          write(*,*) 'current value:',rcp
424          write(*,*) 'enter new value:'
425 124      read(*,*,iostat=ierr) rcp
426          if(ierr.ne.0) goto 124
427          write(*,*)
428          write(*,*) ' rcp (new value):',rcp
429          r=8.314511/(mugaz/1000.0)
430          cpp=r/rcp
431          write(*,*) ' cpp (new value):',cpp
432
433        else if (modif(1:len_trim(modif)).eq.'calc_cpp_mugaz') then
434          write(*,*) 'current value rcp, mugaz:',rcp,mugaz
435          check_cpp_match=.false.
436          force_cpp=.false.
437          call su_gases
438          call calc_cpp_mugaz
439          write(*,*)
440          write(*,*) ' cpp (new value):',cpp
441          write(*,*) ' mugaz (new value):',mugaz
442          r=8.314511/(mugaz/1000.0)
443          rcp=r/cpp
444          write(*,*) ' rcp (new value):',rcp
445         
446        else if (modif(1:len_trim(modif)).eq.'daysec') then
447          write(*,*) 'current value:',daysec
448          write(*,*) 'enter new value:'
449 125      read(*,*,iostat=ierr) daysec
450          if(ierr.ne.0) goto 125
451          write(*,*)
452          write(*,*) ' daysec (new value):',daysec
453
454!         added by RW!
455        else if (modif(1:len_trim(modif)).eq.'year_day') then
456          write(*,*) 'current value:',year_day
457          write(*,*) 'enter new value:'
458 126      read(*,*,iostat=ierr) year_day
459          if(ierr.ne.0) goto 126
460          write(*,*)
461          write(*,*) ' year_day (new value):',year_day
462
463        endif
464      enddo ! of do while(modif(1:1).ne.'hello')
465
466 999  continue
467
468c-----------------------------------------------------------------------
469c       Write values of physical constants after modifications
470c-----------------------------------------------------------------------
471 
472      write(*,*) '*****************************************************'
473      write(*,*) 'Reading tab_cntrl when calling tabfi AFTER changes'
474      write(*,*) '*****************************************************'
475      write(*,5) '(1)        = ngrid?',tab_cntrl(tab0+1),float(ngrid)
476      write(*,5) '(2)            lmax',tab_cntrl(tab0+2),float(lmax)
477      write(*,5) '(3)         day_ini',tab_cntrl(tab0+3),float(day_ini)
478      write(*,5) '(5)             rad',tab_cntrl(tab0+5),rad
479      write(*,5) '(10)         daysec',tab_cntrl(tab0+10),daysec
480      write(*,6) '(6)            omeg',tab_cntrl(tab0+6),omeg
481      write(*,5) '(7)               g',tab_cntrl(tab0+7),g
482      write(*,5) '(8)           mugaz',tab_cntrl(tab0+8),mugaz
483      write(*,5) '(9)             rcp',tab_cntrl(tab0+9),rcp
484      write(*,6) '(11)        dtphys?',tab_cntrl(tab0+11),dtphys
485 
486      write(*,5) '(14)       year_day',tab_cntrl(tab0+14),year_day
487      write(*,5) '(15)       periastr',tab_cntrl(tab0+15),periastr
488      write(*,5) '(16)        apoastr',tab_cntrl(tab0+16),apoastr
489      write(*,5) '(17)       peri_day',tab_cntrl(tab0+17),peri_day
490      write(*,5) '(18)       obliquit',tab_cntrl(tab0+18),obliquit
491 
492      write(*,6) '(19)             z0',tab_cntrl(tab0+19),z0
493      write(*,6) '(21)      emin_turb',tab_cntrl(tab0+21),emin_turb
494      write(*,5) '(20)        lmixmin',tab_cntrl(tab0+20),lmixmin
495 
496      write(*,5) '(26)        emissiv',tab_cntrl(tab0+26),emissiv
497      write(*,5) '(24)     emisice(1)',tab_cntrl(tab0+24),emisice(1)
498      write(*,5) '(25)     emisice(2)',tab_cntrl(tab0+25),emisice(2)
499      write(*,6) '(31)   iceradius(1)',tab_cntrl(tab0+31),iceradius(1)
500      write(*,6) '(32)   iceradius(2)',tab_cntrl(tab0+32),iceradius(2)
501      write(*,5) '(33)   dtemisice(1)',tab_cntrl(tab0+33),dtemisice(1)
502      write(*,5) '(34)   dtemisice(2)',tab_cntrl(tab0+34),dtemisice(2)
503 
504      write(*,5) '(35)        volcapa',tab_cntrl(tab0+35),volcapa
505
506      write(*,*) 
507      write(*,*)
508
509      ENDIF ! of if (Lmodif == 1)
510
511c-----------------------------------------------------------------------
512c       Save some constants for later use (as routine arguments)
513c-----------------------------------------------------------------------
514      p_omeg = omeg
515      p_g = g
516      p_cpp = cpp
517      p_mugaz = mugaz
518      p_daysec = daysec
519      p_rad=rad
520
521
522      end
Note: See TracBrowser for help on using the repository browser.