source: trunk/LMDZ.MARS/libf/phymars/tabfi.F @ 1047

Last change on this file since 1047 was 1047, checked in by emillour, 11 years ago

Mars GCM:

  • IMPORTANT CHANGE: Removed all reference/use of ngridmx (dimphys.h) in routines (necessary prerequisite to using parallel dynamics); in most cases this just means adding 'ngrid' as routine argument, and making local saved variables allocatable (and allocated at first call). In the process, had to convert many *.h files to equivalent modules: yomaer.h => yomaer_h.F90 , surfdat.h => surfdat_h.F90 , comsaison.h => comsaison_h.F90 , yomlw.h => yomlw_h.F90 , comdiurn.h => comdiurn_h.F90 , dimradmars.h => dimradmars_mod.F90 , comgeomfi.h => comgeomfi_h.F90, comsoil.h => comsoil_h.F90 , slope.h => slope_mod.F90
  • Also updated EOF routines, everything is now in eofdump_mod.F90
  • Removed unused routine lectfux.F (in dyn3d)

EM

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