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

Last change on this file since 4201 was 4192, checked in by dubos, 6 years ago

simple_physics : cleanup astronomy

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