source: trunk/mars/libf/phymars/tabfi.F @ 38

Last change on this file since 38 was 38, checked in by emillour, 14 years ago

Ajout du modè Martien (mon LMDZ.MARS.BETA, du 28/01/2011) dans le rértoire mars, pour pouvoir suivre plus facilement les modifs.
EM

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