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

Last change on this file since 601 was 590, checked in by aslmd, 13 years ago

LMDZ.GENERIC: Introduced global1d in callcorrk so that global (using sza) or local (using latitude) 1D simulations can be carried out. Converted all astronomical distances in AU instead of Mkm. This might cause problems with old start files. So added a test in iniorbit. A quite dirty test, but thatll do the job.

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