source: trunk/LMDZ.UNIVERSAL/libf/phygeneric/iniphysiq.F @ 1000

Last change on this file since 1000 was 844, checked in by aslmd, 12 years ago

LMDZ.GENERIC. Added a new folder for the interface with LMDZ.COMMON and LMDZ5

File size: 6.3 KB
Line 
1!
2! $Id: iniphysiq.F 1403 2010-07-01 09:02:53Z fairhead $
3!
4c
5c
6      SUBROUTINE iniphysiq(ngrid,nlayer,
7     $           punjours,
8     $           pdayref,ptimestep,
9     $           plat,plon,parea,pcu,pcv,
10     $           prad,pg,pr,pcpp,iflag_phys)
11      USE dimphy
12      USE mod_grid_phy_lmdz
13      USE mod_phys_lmdz_para
14      USE comgeomphy
15
16      USE infotrac, only: nqtot
17
18#ifdef CPP_IOIPSL
19      use IOIPSL
20#else
21! if not using IOIPSL, we still need to use (a local version of) getin
22      use ioipsl_getincom
23#endif
24
25      IMPLICIT NONE
26c
27c=======================================================================
28c
29c   subject:
30c   --------
31c
32c   Initialisation for the physical parametrisations of the LMD
33c   martian atmospheric general circulation modele.
34c
35c   author: Frederic Hourdin 15 / 10 /93
36c   -------
37c
38c   arguments:
39c   ----------
40c
41c   input:
42c   ------
43c
44c    ngrid                 Size of the horizontal grid.
45c                          All internal loops are performed on that grid.
46c    nlayer                Number of vertical layers.
47c    pdayref               Day of reference for the simulation
48c    firstcall             True at the first call
49c    lastcall              True at the last call
50c    pday                  Number of days counted from the North. Spring
51c                          equinoxe.
52c
53c=======================================================================
54c
55c AS: modified for generic physiq
56c
57c-----------------------------------------------------------------------
58c   declarations:
59c   -------------
60 
61cym#include "dimensions.h"
62cym#include "dimphy.h"
63cym#include "comgeomphy.h"
64
65#include "dimensions.h"
66#include "dimphys.h" 
67!#include "advtrac.h" 
68!iadv is already in infotrac but not invoked here
69#include "control.h"
70
71      REAL prad,pg,pr,pcpp,punjours
72 
73      INTEGER ngrid,nlayer
74      !REAL plat(ngrid),plon(ngrid),parea(klon_glo)
75      REAL plat(ngrid),plon(ngrid),parea(ngrid)
76      REAL pcu(ngrid),pcv(ngrid)
77      INTEGER pdayref
78      INTEGER :: ibegin,iend,offset
79      INTEGER,INTENT(IN) :: iflag_phys ! type of physics to be called
80
81      INTEGER :: ngrid_sub
82 
83      REAL ptimestep
84      CHARACTER (LEN=20) :: modname='iniphysiq'
85      CHARACTER (LEN=80) :: abort_message
86
87      IF (nlayer.NE.klev) THEN
88         PRINT*,'STOP in iniphysiq'
89         PRINT*,'Probleme de dimensions :'
90         PRINT*,'nlayer     = ',nlayer
91         PRINT*,'klev   = ',klev
92         abort_message = ''
93         CALL abort_gcm (modname,abort_message,1)
94      ENDIF
95
96      ngrid_sub = klon_mpi_end - klon_mpi_begin + 1
97      IF (ngrid_sub.NE.klon) THEN
98         PRINT*,'STOP in iniphysiq'
99         PRINT*,'Probleme de dimensions :'
100         PRINT*,'ngrid     = ', ngrid_sub
101         PRINT*,'klon   = ', klon
102         abort_message = ''
103         CALL abort_gcm (modname,abort_message,1)
104      ENDIF
105
106      !!!! WE HAVE TO FILL control.h FOR GENERIC PHYSICS
107      !!! -- NOT USED: periodav, nday, iperiod, iconser, idissip, anneeref
108      !!! -- NEEDED : day_step, iphysiq, ecritphy
109          !!!! 1. not done in conf_gcm
110          ecritphy=1
111          call getin("ecritphy",ecritphy)
112          PRINT*,"ecritphy = ",ecritphy
113          !!!! 2. done in conf_gcm, present in control_mod,
114          !!!!    but conflict if both control_mod.F90 and control.h!
115          day_step=240
116          call getin("day_step",day_step)
117          PRINT*,"day_step = ",day_step
118          iphysiq = 5
119          call getin("iphysiq",iphysiq)
120          PRINT*,"iphysiq = ",iphysiq
121
122c$OMP PARALLEL PRIVATE(ibegin,iend)
123c$OMP+         SHARED(parea,pcu,pcv,plon,plat)
124     
125      offset=klon_mpi_begin-1
126      airephy(1:klon_omp)=parea(offset+klon_omp_begin:
127     &                          offset+klon_omp_end)
128      cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
129      cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
130      rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
131      rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
132
133      !call suphel
134      print*,'not earth physics. we do not call suphel.'
135
136c$OMP END PARALLEL
137
138      !print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
139      !print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
140      !print*, "BEFORE CORREC....", RA, RG, RD, RCPD
141      !print*, '------------------'
142      !print*, 'RAD ', prad, RA, 100.*abs((prad - RA)/RA)
143      !if (100.*abs((prad - RA)/RA) .gt. 0.1) RA = prad
144      !print*, '------------------'
145      !print*, 'G ', pg, RG, 100.*abs((pg - RG)/RG)
146      !if (100.*abs((pg - RG)/RG) .gt. 0.1) RG = pg
147      !print*, '------------------'
148      !print*, 'R ', pr, RD, 100.*abs((pr - RD)/RD)
149      !if (100.*abs((pr - RD)/RD) .gt. 0.1) RD = pr
150      !print*, '------------------'
151      !print*, 'CP ', pcpp, RCPD, 100.*abs((pcpp - RCPD)/RCPD)
152      !if (100.*abs((pcpp - RCPD)/RCPD) .gt. 0.1) RCPD = pcpp
153      !print*, "AFTER CORREC....", RA, RG, RD, RCPD
154     
155      print*,'agagagagagagagagaga'
156      print*,'klon_mpi_begin =', klon_mpi_begin
157      print*,'klon_mpi_end =', klon_mpi_end
158      print*,'klon_mpi =', klon_mpi
159      print*,'klon_mpi_para_nb =', klon_mpi_para_nb
160      print*,'klon_mpi_para_begin =', klon_mpi_para_begin
161      print*,'klon_mpi_para_end  =', klon_mpi_para_end
162      print*,'mpi_rank =', mpi_rank
163      print*,'mpi_size =', mpi_size
164      print*,'mpi_root =', mpi_root
165      print*,'klon_glo =', klon_glo
166      print*,'is_mpi_root =',is_mpi_root
167      print*,'is_omp_root =',is_omp_root
168
169      !!! AS: CALL inifis (previously done in calfis in planeto version of GCM)
170      !!!   punjours --> daysec
171      !!!   pdayref --> day_ini
172      print*, "START INIFIS !!!!"
173         call inifis(klon,nlayer,
174     $           pdayref,punjours,ptimestep,
175     $           plat(klon_mpi_begin:klon_mpi_end),
176     $           plon(klon_mpi_begin:klon_mpi_end),
177     $           parea(klon_mpi_begin:klon_mpi_end),
178     $           prad,pg,pr,pcpp)
179      print*, "END INIFIS !!!!"
180
181      !! this is an addition to dimphys.h
182      !! initialized in inifis for sequential runs with previous dyn core
183      !! modified here for parallel runs
184      cursor = klon_mpi_begin
185      print*, "CURSOR !!!!", mpi_rank, cursor
186
187      !!OKOKOKOKOK
188      !!print*, plat,plon,parea,prad,pg,pr,pcpp
189
190!      RETURN
191!9999  CONTINUE
192!      abort_message ='Cette version demande les fichier rnatur.dat
193!     & et surf.def'
194!      CALL abort_gcm (modname,abort_message,1)
195
196      END
Note: See TracBrowser for help on using the repository browser.