source: codes/icosagcm/branches/SATURN_DYNAMICO/LMDZ.COMMON/libf/phystd/tabfi.F @ 227

Last change on this file since 227 was 227, checked in by milmd, 10 years ago

Last LMDZ version (1315) with OpenMP directives and other stuff

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