source: dynamico_lmdz/simple_physics/phyparam/param/iniphyparam.F @ 4219

Last change on this file since 4219 was 4219, checked in by dubos, 5 years ago

simple_physics : removed unused files

File size: 6.4 KB
Line 
1      SUBROUTINE iniphyparam(ngrid,nlayer,
2     $           punjours,
3     $           pdayref,ptimestep,
4     $           prad,pg,pr,pcpp)
5      use IOIPSL
6      use getparam
7      use dimphy
8      USE mod_grid_phy_lmdz
9      USE mod_phys_lmdz_para
10      USE callkeys
11      use comgeomfi
12      USE geometry_mod, ONLY : longitude,latitude,cell_area
13      USE phys_const, ONLY : planet_rad,g,r,cpp,rcp,dtphys,unjours,mugaz
14      USE planet, ONLY : coefir, coefvis
15      USE astronomy
16      USE turbulence, ONLY : lmixmin, emin_turb
17      USE surface
18      IMPLICIT NONE
19
20c
21c=======================================================================
22c
23c   subject:
24c   --------
25c
26c   Initialisation for the physical parametrisations of the LMD
27c   martian atmospheric general circulation modele.
28c
29c   author: Frederic Hourdin 15 / 10 /93
30c   -------
31c
32c   arguments:
33c   ----------
34c
35c   input:
36c   ------
37c
38c    ngrid                 Size of the horizontal grid.
39c                          All internal loops are performed on that grid.
40c    nlayer                Number of vertical layers.
41c    pdayref               Day of reference for the simulation
42c    firstcall             True at the first call
43c    lastcall              True at the last call
44c    pday                  Number of days counted from the North. Spring
45c                          equinoxe.
46c
47c=======================================================================
48c
49c-----------------------------------------------------------------------
50c   declarations:
51c   -------------
52
53 
54#include "iniprint.h"
55
56
57      REAL prad,pg,pr,pcpp,punjours
58 
59      INTEGER ngrid,nlayer
60      REAL pdayref
61 
62      REAL ptimestep
63 
64      EXTERNAL inifrict
65 
66      print*,'INIPHYPARAM'
67
68      CALL init_comgeomfi(klon_omp, klev, longitude, latitude)
69
70      IF (klon.NE.klon_omp) THEN
71         PRINT*,'STOP in iniphyparam'
72         PRINT*,'Probleme de dimensions :'
73         PRINT*,'klon     = ',klon
74         PRINT*,'klon_omp   = ',klon_omp
75         STOP
76      ENDIF
77
78      IF (nlayer.NE.nlayermx) THEN
79         PRINT*,'STOP in iniphyparam'
80         PRINT*,'Probleme de dimensions :'
81         PRINT*,'nlayer     = ',nlayer
82         PRINT*,'nlayermx   = ',nlayermx
83         STOP
84      ENDIF
85
86      IF (ngrid.NE.klon_glo) THEN
87         PRINT*,'STOP in iniphyparam'
88         PRINT*,'Probleme de dimensions :'
89         PRINT*,'ngrid     = ',ngrid
90         PRINT*,'ngridmax   = ',klon_glo
91        STOP
92      ENDIF
93
94      print*,'Avant les getpar '
95      CALL getpar('unjours',86400.  ,unjours,'unjours')
96      CALL getpar('planet_rad',6.4e6,planet_rad,'planet_rad')
97      CALL getpar('g',9.8           ,g,'g')
98      CALL getpar('cpp',1004.       ,cpp,'cpp')
99      CALL getpar('mugaz',28.       ,mugaz,'mugaz')
100      CALL getpar('year_day',360.   ,year_day,'year_day')
101      CALL getpar('periheli',150.   ,periheli,'periheli')
102      CALL getpar('aphelie',150.    ,aphelie,'aphelie')
103      CALL getpar('peri_day',0.     ,peri_day,'peri_day')
104      CALL getpar('obliquit',23.    ,obliquit,'obliquit')
105      CALL getpar('Cd_mer',.01      ,Cd_mer,'Cd_mer')
106      CALL getpar('Cd_ter',.01      ,Cd_ter,'Cd_ter')
107      CALL getpar('I_mer',30000.    ,I_mer,'I_mer')
108      CALL getpar('I_ter',30000.    ,I_ter,'I_ter')
109      CALL getpar('alb_ter',.112    ,alb_ter,'alb_ter')
110      CALL getpar('alb_mer',.112    ,alb_mer,'alb_mer')
111      CALL getpar('emi_mer',1.      ,emi_mer,'emi_mer')
112      CALL getpar('emi_mer',1.      ,emi_mer,'emi_mer')
113      CALL getpar('emin_turb',1.e-16 ,emin_turb,'emin_turb')
114      CALL getpar('lmixmin',100.    ,lmixmin,'lmixmin')
115      CALL getpar('coefvis',.99     ,coefvis,'coefvis')
116      CALL getpar('coefir',.08      ,coefir,'coefir')
117
118
119      CALL getpar('callrad',.true.,callrad,'appel rayonnemen')
120      CALL getpar('calldifv',.true.,calldifv,'appel difv')
121      CALL getpar('calladj',.true.,calladj,'appel adj')
122      CALL getpar('callcond',.true.,callcond,'appel cond')
123      CALL getpar('callsoil',.true.,callsoil,'appel soil')
124      CALL getpar('season',.true.,season,'appel soil')
125      CALL getpar('diurnal',.false.,diurnal,'appel soil')
126      CALL getpar('lverbose',.true.,lverbose,'appel soil')
127      CALL getpar('period_sort',1.,period_sort,'period sorties en jour')
128
129      write(lunout,*) 'unjours=',unjours
130      write(lunout,*) 'planet_rad=',planet_rad
131      write(lunout,*) 'g=',g
132      write(lunout,*) 'cpp=',cpp
133      write(lunout,*) 'mugaz=',mugaz
134      write(lunout,*) 'year_day=',year_day
135      write(lunout,*) 'periheli=',periheli
136      write(lunout,*) 'aphelie=',aphelie
137      write(lunout,*) 'peri_day=',peri_day
138      write(lunout,*) 'obliquit=',obliquit
139      write(lunout,*) 'Cd_mer=',Cd_mer
140      write(lunout,*) 'Cd_ter=',Cd_ter
141      write(lunout,*) 'I_mer=',I_mer
142      write(lunout,*) 'I_ter=',I_ter
143      write(lunout,*) 'alb_ter=',alb_ter
144      write(lunout,*) 'alb_mer=',alb_mer
145      write(lunout,*) 'emi_mer=',emi_mer
146      write(lunout,*) 'emi_mer=',emi_mer
147      write(lunout,*) 'emin_turb=',emin_turb
148      write(lunout,*) 'lmixmin=',lmixmin
149      write(lunout,*) 'coefvis=',coefvis
150      write(lunout,*) 'coefir=',coefir
151      write(lunout,*) 'callrad=',callrad
152      write(lunout,*) 'calldifv=',calldifv
153      write(lunout,*) 'calladj=',calladj
154      write(lunout,*) 'callcond=',callcond
155      write(lunout,*) 'callsoil=',callsoil
156      write(lunout,*) 'season=',season
157      write(lunout,*) 'diurnal=',diurnal
158      write(lunout,*) 'lverbose=',lverbose
159      write(lunout,*) 'period_sort=',period_sort
160
161      print*,'Activation de la physique:'
162      print*,' Rayonnement ',callrad
163      print*,' Diffusion verticale turbulente ', calldifv
164      print*,' Ajustement convectif ',calladj
165      print*,' Sol ',callsoil
166      print*,' Cycle diurne ',diurnal
167
168c   choice of the frequency of the computation of radiations
169      IF(diurnal) THEN
170         iradia=NINT(punjours/(20.*ptimestep))
171      ELSE
172         iradia=NINT(punjours/(4.*ptimestep))
173      ENDIF
174      iradia=1
175      PRINT*,'unjours',punjours
176      PRINT*,'The radiative transfer is computed each ',
177     s   iradia,' physical time-step or each ',
178     s   iradia*ptimestep,' seconds'
179c-----------------------------------------------------------------------
180
181      print*,'latitude0  ohe',latitude(1:3),latitude(klon_omp)
182      print*,'OK17 AAA'
183
184      prad=planet_rad
185      pg=g
186      r=8.134/(mugaz*0.001)
187      print*,'R=',r
188      pr=r
189      pcpp=cpp
190      rcp=r/cpp
191      dtphys=ptimestep
192      punjours=unjours
193
194      RETURN
1959999  STOP'Cette version demande les fichier rnatur.dat et surf.def'
196      END
Note: See TracBrowser for help on using the repository browser.