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

Last change on this file since 747 was 726, checked in by jleconte, 12 years ago

17/07/2012 == JL for LK

  • Generalization of aerosol scheme:
    • any number of aerosols can be used and id numbers are determined consistently by the code. Aerosol order not important anymore.
    • addition of a module with the id numbers for aerosols (aerosol_mod.F90).
    • initialization of aerosols id numbers in iniaerosol.F90
    • compile with -s x where x *must* be equal to the number of aerosols turned on in callphys.def (either by a flag or by dusttau>0 for dust). => may have to erase object files when compiling with s option for the first time.
  • For no aerosols, run with aeroco2=.true. and aerofixco2=.true (the default distribution for fixed co2

aerosols is 1.e-9; can be changed in aeropacity).

  • If starting from an old start file, recreate start file with the q=0 option in newstart.e.
  • update callphys.def with aeroXXX and aerofixXXX options (only XXX=co2,h2o supported for

now). Dust is activated by setting dusttau>0. See the early mars case in deftank.

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