source: trunk/LMDZ.GENERIC/libf/phystd/for_lmdz5/iniphysiq.F @ 836

Last change on this file since 836 was 832, checked in by aslmd, 12 years ago

LMDZ.GENERIC. stuff to run in parallel with LMDZ5. transparent to casual user (in a folder for_lmdz5).

File size: 6.2 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)
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
80      INTEGER :: ngrid_sub
81 
82      REAL ptimestep
83      CHARACTER (LEN=20) :: modname='iniphysiq'
84      CHARACTER (LEN=80) :: abort_message
85
86      IF (nlayer.NE.klev) THEN
87         PRINT*,'STOP in iniphysiq'
88         PRINT*,'Probleme de dimensions :'
89         PRINT*,'nlayer     = ',nlayer
90         PRINT*,'klev   = ',klev
91         abort_message = ''
92         CALL abort_gcm (modname,abort_message,1)
93      ENDIF
94
95      ngrid_sub = klon_mpi_end - klon_mpi_begin + 1
96      IF (ngrid_sub.NE.klon) THEN
97         PRINT*,'STOP in iniphysiq'
98         PRINT*,'Probleme de dimensions :'
99         PRINT*,'ngrid     = ', ngrid_sub
100         PRINT*,'klon   = ', klon
101         abort_message = ''
102         CALL abort_gcm (modname,abort_message,1)
103      ENDIF
104
105      !!!! WE HAVE TO FILL control.h FOR GENERIC PHYSICS
106      !!! -- NOT USED: periodav, nday, iperiod, iconser, idissip, anneeref
107      !!! -- NEEDED : day_step, iphysiq, ecritphy
108          !!!! 1. not done in conf_gcm
109          ecritphy=1
110          call getin("ecritphy",ecritphy)
111          PRINT*,"ecritphy = ",ecritphy
112          !!!! 2. done in conf_gcm, present in control_mod,
113          !!!!    but conflict if both control_mod.F90 and control.h!
114          day_step=240
115          call getin("day_step",day_step)
116          PRINT*,"day_step = ",day_step
117          iphysiq = 5
118          call getin("iphysiq",iphysiq)
119          PRINT*,"iphysiq = ",iphysiq
120
121c$OMP PARALLEL PRIVATE(ibegin,iend)
122c$OMP+         SHARED(parea,pcu,pcv,plon,plat)
123     
124      offset=klon_mpi_begin-1
125      airephy(1:klon_omp)=parea(offset+klon_omp_begin:
126     &                          offset+klon_omp_end)
127      cuphy(1:klon_omp)=pcu(offset+klon_omp_begin:offset+klon_omp_end)
128      cvphy(1:klon_omp)=pcv(offset+klon_omp_begin:offset+klon_omp_end)
129      rlond(1:klon_omp)=plon(offset+klon_omp_begin:offset+klon_omp_end)
130      rlatd(1:klon_omp)=plat(offset+klon_omp_begin:offset+klon_omp_end)
131
132      !call suphel
133      print*,'not earth physics. we do not call suphel.'
134
135c$OMP END PARALLEL
136
137      !print*,'ATTENTION !!! TRAVAILLER SUR INIPHYSIQ'
138      !print*,'CONTROLE DES LATITUDES, LONGITUDES, PARAMETRES ...'
139      !print*, "BEFORE CORREC....", RA, RG, RD, RCPD
140      !print*, '------------------'
141      !print*, 'RAD ', prad, RA, 100.*abs((prad - RA)/RA)
142      !if (100.*abs((prad - RA)/RA) .gt. 0.1) RA = prad
143      !print*, '------------------'
144      !print*, 'G ', pg, RG, 100.*abs((pg - RG)/RG)
145      !if (100.*abs((pg - RG)/RG) .gt. 0.1) RG = pg
146      !print*, '------------------'
147      !print*, 'R ', pr, RD, 100.*abs((pr - RD)/RD)
148      !if (100.*abs((pr - RD)/RD) .gt. 0.1) RD = pr
149      !print*, '------------------'
150      !print*, 'CP ', pcpp, RCPD, 100.*abs((pcpp - RCPD)/RCPD)
151      !if (100.*abs((pcpp - RCPD)/RCPD) .gt. 0.1) RCPD = pcpp
152      !print*, "AFTER CORREC....", RA, RG, RD, RCPD
153     
154      print*,'agagagagagagagagaga'
155      print*,'klon_mpi_begin =', klon_mpi_begin
156      print*,'klon_mpi_end =', klon_mpi_end
157      print*,'klon_mpi =', klon_mpi
158      print*,'klon_mpi_para_nb =', klon_mpi_para_nb
159      print*,'klon_mpi_para_begin =', klon_mpi_para_begin
160      print*,'klon_mpi_para_end  =', klon_mpi_para_end
161      print*,'mpi_rank =', mpi_rank
162      print*,'mpi_size =', mpi_size
163      print*,'mpi_root =', mpi_root
164      print*,'klon_glo =', klon_glo
165      print*,'is_mpi_root =',is_mpi_root
166      print*,'is_omp_root =',is_omp_root
167
168      !!! AS: CALL inifis (previously done in calfis in planeto version of GCM)
169      !!!   punjours --> daysec
170      !!!   pdayref --> day_ini
171      print*, "START INIFIS !!!!"
172         call inifis(klon,nlayer,
173     $           pdayref,punjours,ptimestep,
174     $           plat(klon_mpi_begin:klon_mpi_end),
175     $           plon(klon_mpi_begin:klon_mpi_end),
176     $           parea(klon_mpi_begin:klon_mpi_end),
177     $           prad,pg,pr,pcpp)
178      print*, "END INIFIS !!!!"
179
180      !! this is an addition to dimphys.h
181      !! initialized in inifis for sequential runs with previous dyn core
182      !! modified here for parallel runs
183      cursor = klon_mpi_begin
184      print*, "CURSOR !!!!", mpi_rank, cursor
185
186      !!OKOKOKOKOK
187      !!print*, plat,plon,parea,prad,pg,pr,pcpp
188
189      RETURN
1909999  CONTINUE
191      abort_message ='Cette version demande les fichier rnatur.dat
192     & et surf.def'
193      CALL abort_gcm (modname,abort_message,1)
194
195      END
Note: See TracBrowser for help on using the repository browser.