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

Last change on this file since 649 was 649, checked in by jleconte, 13 years ago
  • Correction a huge bug in newstart: rcp and cpp can now be changed in start.nc files and are the same as in startfi.nc;

Even when starting from start and startfi files.

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