source: LMDZ4/branches/LMDZ4_V3_patches/libf/phylmd/surf_land_orchidee_mod.F90 @ 1415

Last change on this file since 1415 was 1073, checked in by Laurent Fairhead, 15 years ago

Mise a jour de la branche par rapport au depot CVS
JG/LF

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 23.7 KB
RevLine 
[781]1!
2MODULE surf_land_orchidee_mod
3!
4! This module controles the interface towards the model ORCHIDEE
5!
6! Subroutines in this module : surf_land_orchidee
7!                              Init_orchidee_index
8!                              Get_orchidee_communicator
9!                              Init_neighbours
10#ifdef CPP_VEGET
11
12  USE dimphy
13  USE intersurf     ! module d'ORCHIDEE
14  USE cpl_mod,      ONLY : cpl_send_land_fields
15  USE surface_data, ONLY : ocean, ok_veget
16  USE comgeomphy,   ONLY : cuphy, cvphy
17  USE mod_grid_phy_lmdz
18  USE mod_phys_lmdz_para
19
20  IMPLICIT NONE
21
22  PRIVATE
23  PUBLIC  :: surf_land_orchidee
24
25CONTAINS
26!
27!****************************************************************************************
28
29  SUBROUTINE surf_land_orchidee(itime, dtime, date0, knon, &
30       knindex, rlon, rlat, pctsrf, &
31       debut, lafin, &
32       plev,  u1_lay, v1_lay, temp_air, spechum, epot_air, ccanopy, &
33       tq_cdrag, petAcoef, peqAcoef, petBcoef, peqBcoef, &
34       precip_rain, precip_snow, lwdown, swnet, swdown, &
35       ps, &
36       evap, fluxsens, fluxlat, &             
37       tsol_rad, tsurf_new, alb_new, alblw, &
38       emis_new, z0_new, qsurf)
39!   
40! Cette routine sert d'interface entre le modele atmospherique et le
41! modele de sol continental. Appel a sechiba
42!
43! L. Fairhead 02/2000
44!
45! input:
46!   itime        numero du pas de temps
47!   dtime        pas de temps de la physique (en s)
48!   nisurf       index de la surface a traiter (1 = sol continental)
49!   knon         nombre de points de la surface a traiter
50!   knindex      index des points de la surface a traiter
51!   rlon         longitudes de la grille entiere
52!   rlat         latitudes de la grille entiere
53!   pctsrf       tableau des fractions de surface de chaque maille
54!   debut        logical: 1er appel a la physique (lire les restart)
55!   lafin        logical: dernier appel a la physique (ecrire les restart)
56!                     (si false calcul simplifie des fluxs sur les continents)
57!   plev         hauteur de la premiere couche (Pa)     
58!   u1_lay       vitesse u 1ere couche
59!   v1_lay       vitesse v 1ere couche
60!   temp_air     temperature de l'air 1ere couche
61!   spechum      humidite specifique 1ere couche
62!   epot_air     temp pot de l'air
63!   ccanopy      concentration CO2 canopee
64!   tq_cdrag     cdrag
65!   petAcoef     coeff. A de la resolution de la CL pour t
66!   peqAcoef     coeff. A de la resolution de la CL pour q
67!   petBcoef     coeff. B de la resolution de la CL pour t
68!   peqBcoef     coeff. B de la resolution de la CL pour q
69!   precip_rain  precipitation liquide
70!   precip_snow  precipitation solide
71!   lwdown       flux IR descendant a la surface
72!   swnet        flux solaire net
73!   swdown       flux solaire entrant a la surface
74!   ps           pression au sol
75!   radsol       rayonnement net aus sol (LW + SW)
76!   
77!
78! output:
79!   evap         evaporation totale
80!   fluxsens     flux de chaleur sensible
81!   fluxlat      flux de chaleur latente
82!   tsol_rad     
83!   tsurf_new    temperature au sol
84!   alb_new      albedo
85!   emis_new     emissivite
86!   z0_new       surface roughness
87!   qsurf        air moisture at surface
88!
89    INCLUDE "indicesol.h"
[793]90    INCLUDE "temps.h"
91    INCLUDE "YOMCST.h"
[781]92    INCLUDE "iniprint.h"
[793]93    INCLUDE "dimensions.h"
[781]94 
95!
96! Parametres d'entree
97!****************************************************************************************
98    INTEGER, INTENT(IN)                       :: itime
99    REAL, INTENT(IN)                          :: dtime
100    REAL, INTENT(IN)                          :: date0
101    INTEGER, INTENT(IN)                       :: knon
102    INTEGER, DIMENSION(klon), INTENT(IN)      :: knindex
103    LOGICAL, INTENT(IN)                       :: debut, lafin
104    REAL, DIMENSION(klon,nbsrf), INTENT(IN)   :: pctsrf
105    REAL, DIMENSION(klon), INTENT(IN)         :: rlon, rlat
106    REAL, DIMENSION(klon), INTENT(IN)         :: plev
107    REAL, DIMENSION(klon), INTENT(IN)         :: u1_lay, v1_lay
108    REAL, DIMENSION(klon), INTENT(IN)         :: temp_air, spechum
109    REAL, DIMENSION(klon), INTENT(IN)         :: epot_air, ccanopy
110    REAL, DIMENSION(klon), INTENT(IN)         :: tq_cdrag
111    REAL, DIMENSION(klon), INTENT(IN)         :: petAcoef, peqAcoef
112    REAL, DIMENSION(klon), INTENT(IN)         :: petBcoef, peqBcoef
113    REAL, DIMENSION(klon), INTENT(IN)         :: precip_rain, precip_snow
114    REAL, DIMENSION(klon), INTENT(IN)         :: lwdown, swnet, swdown, ps
115    REAL, DIMENSION(klon)                     :: swdown_vrai
116
117! Parametres de sortie
118!****************************************************************************************
119    REAL, DIMENSION(klon), INTENT(OUT)        :: evap, fluxsens, fluxlat, qsurf
120    REAL, DIMENSION(klon), INTENT(OUT)        :: tsol_rad, tsurf_new, alb_new, alblw
121    REAL, DIMENSION(klon), INTENT(OUT)        :: emis_new, z0_new
122
123! Local
124!****************************************************************************************
125    INTEGER                                   :: ij, jj, igrid, ireal, index
126    INTEGER                                   :: error
127    CHARACTER (len = 20)                      :: modname = 'surf_land_orchidee'
128    CHARACTER (len = 80)                      :: abort_message
129    LOGICAL,SAVE                              :: check = .FALSE.
130    !$OMP THREADPRIVATE(check)
131
132! type de couplage dans sechiba
133!  character (len=10)   :: coupling = 'implicit'
134! drapeaux controlant les appels dans SECHIBA
135!  type(control_type), save   :: control_in
136! Preserved albedo
137    REAL, ALLOCATABLE, DIMENSION(:), SAVE     :: albedo_keep, zlev
138    !$OMP THREADPRIVATE(albedo_keep,zlev)
139! coordonnees geographiques
140    REAL, ALLOCATABLE, DIMENSION(:,:), SAVE   :: lalo
141    !$OMP THREADPRIVATE(lalo)
142! pts voisins
143    INTEGER,ALLOCATABLE, DIMENSION(:,:), SAVE :: neighbours
144    !$OMP THREADPRIVATE(neighbours)
145! fractions continents
146    REAL,ALLOCATABLE, DIMENSION(:), SAVE      :: contfrac
147    !$OMP THREADPRIVATE(contfrac)
148! resolution de la grille
149    REAL, ALLOCATABLE, DIMENSION (:,:), SAVE  :: resolution
150    !$OMP THREADPRIVATE(resolution)
151
152    REAL, ALLOCATABLE, DIMENSION (:,:), SAVE  :: lon_scat, lat_scat 
153    !$OMP THREADPRIVATE(lon_scat,lat_scat)
154
155    LOGICAL, SAVE                             :: lrestart_read = .TRUE.
156    !$OMP THREADPRIVATE(lrestart_read)
157    LOGICAL, SAVE                             :: lrestart_write = .FALSE.
158    !$OMP THREADPRIVATE(lrestart_write)
159
160    REAL, DIMENSION(knon,2)                   :: albedo_out
161    !$OMP THREADPRIVATE(albedo_out)
162
163! Pb de nomenclature
164    REAL, DIMENSION(klon)                     :: petA_orc, peqA_orc
165    REAL, DIMENSION(klon)                     :: petB_orc, peqB_orc
166! Pb de correspondances de grilles
167    INTEGER, DIMENSION(:), SAVE, ALLOCATABLE  :: ig, jg
168    !$OMP THREADPRIVATE(ig,jg)
169    INTEGER :: indi, indj
170    INTEGER, SAVE, ALLOCATABLE,DIMENSION(:)   :: ktindex
171    !$OMP THREADPRIVATE(ktindex)
172
173! Essai cdrag
174    REAL, DIMENSION(klon)                     :: cdrag
175    INTEGER,SAVE                              :: offset
176    !$OMP THREADPRIVATE(offset)
177
178    REAL, DIMENSION(klon_glo)                 :: rlon_g,rlat_g
179    INTEGER, SAVE                             :: orch_comm
180    !$OMP THREADPRIVATE(orch_comm)
181
182    REAL, ALLOCATABLE, DIMENSION(:), SAVE     :: coastalflow
183    !$OMP THREADPRIVATE(coastalflow)
184    REAL, ALLOCATABLE, DIMENSION(:), SAVE     :: riverflow
185    !$OMP THREADPRIVATE(riverflow)
186!
187! Fin definition
188!****************************************************************************************
189
190    IF (check) WRITE(lunout,*)'Entree ', modname
191    IF (check) WRITE(lunout,*)'ok_veget = ',ok_veget
192 
193! Initialisation
194 
195    IF (debut) THEN
196       ALLOCATE(ktindex(knon))
197       IF ( .NOT. ALLOCATED(albedo_keep)) THEN
198          ALLOCATE(albedo_keep(klon))
199          ALLOCATE(zlev(knon))
200       ENDIF
201! Pb de correspondances de grilles
202       ALLOCATE(ig(klon))
203       ALLOCATE(jg(klon))
204       ig(1) = 1
205       jg(1) = 1
206       indi = 0
207       indj = 2
208       DO igrid = 2, klon - 1
209          indi = indi + 1
210          IF ( indi > iim) THEN
211             indi = 1
212             indj = indj + 1
213          ENDIF
214          ig(igrid) = indi
215          jg(igrid) = indj
216       ENDDO
217       ig(klon) = 1
218       jg(klon) = jjm + 1
219
220       IF ((.NOT. ALLOCATED(lalo))) THEN
221          ALLOCATE(lalo(knon,2), stat = error)
222          IF (error /= 0) THEN
223             abort_message='Pb allocation lalo'
224             CALL abort_gcm(modname,abort_message,1)
225          ENDIF
226       ENDIF
227       IF ((.NOT. ALLOCATED(lon_scat))) THEN
228          ALLOCATE(lon_scat(iim,jjm+1), stat = error)
229          IF (error /= 0) THEN
230             abort_message='Pb allocation lon_scat'
231             CALL abort_gcm(modname,abort_message,1)
232          ENDIF
233       ENDIF
234       IF ((.NOT. ALLOCATED(lat_scat))) THEN
235          ALLOCATE(lat_scat(iim,jjm+1), stat = error)
236          IF (error /= 0) THEN
237             abort_message='Pb allocation lat_scat'
238             CALL abort_gcm(modname,abort_message,1)
239          ENDIF
240       ENDIF
241       lon_scat = 0.
242       lat_scat = 0.
243       DO igrid = 1, knon
244          index = knindex(igrid)
245          lalo(igrid,2) = rlon(index)
246          lalo(igrid,1) = rlat(index)
247       ENDDO
248
249       
250       
251       CALL Gather(rlon,rlon_g)
252       CALL Gather(rlat,rlat_g)
253
254       IF (is_mpi_root) THEN
255          index = 1
256          DO jj = 2, jjm
257             DO ij = 1, iim
258                index = index + 1
259                lon_scat(ij,jj) = rlon_g(index)
260                lat_scat(ij,jj) = rlat_g(index)
261             ENDDO
262          ENDDO
263          lon_scat(:,1) = lon_scat(:,2)
264          lat_scat(:,1) = rlat_g(1)
265          lon_scat(:,jjm+1) = lon_scat(:,2)
266          lat_scat(:,jjm+1) = rlat_g(klon_glo)
267       ENDIF
268   
[1073]269       CALL bcast(lon_scat)
270       CALL bcast(lat_scat)
[781]271
272!
273! Allouer et initialiser le tableau des voisins et des fraction de continents
274!
275       IF ( (.NOT.ALLOCATED(neighbours))) THEN
276          ALLOCATE(neighbours(knon,8), stat = error)
277          IF (error /= 0) THEN
278             abort_message='Pb allocation neighbours'
279             CALL abort_gcm(modname,abort_message,1)
280          ENDIF
281       ENDIF
282       neighbours = -1.
283       IF (( .NOT. ALLOCATED(contfrac))) THEN
284          ALLOCATE(contfrac(knon), stat = error)
285          IF (error /= 0) THEN
286             abort_message='Pb allocation contfrac'
287             CALL abort_gcm(modname,abort_message,1)
288          ENDIF
289       ENDIF
290
291       DO igrid = 1, knon
292          ireal = knindex(igrid)
293          contfrac(igrid) = pctsrf(ireal,is_ter)
294       ENDDO
295
296
297       CALL Init_neighbours(knon,neighbours,knindex,pctsrf(:,is_ter))
298
299!
300!  Allocation et calcul resolutions
301       IF ( (.NOT.ALLOCATED(resolution))) THEN
302          ALLOCATE(resolution(knon,2), stat = error)
303          IF (error /= 0) THEN
304             abort_message='Pb allocation resolution'
305             CALL abort_gcm(modname,abort_message,1)
306          ENDIF
307       ENDIF
308       DO igrid = 1, knon
309          ij = knindex(igrid)
310          resolution(igrid,1) = cuphy(ij)
311          resolution(igrid,2) = cvphy(ij)
312       ENDDO
313     
314       ALLOCATE(coastalflow(klon), stat = error)
315       IF (error /= 0) THEN
316          abort_message='Pb allocation coastalflow'
317          CALL abort_gcm(modname,abort_message,1)
318       ENDIF
319       
320       ALLOCATE(riverflow(klon), stat = error)
321       IF (error /= 0) THEN
322          abort_message='Pb allocation riverflow'
323          CALL abort_gcm(modname,abort_message,1)
324       ENDIF
325
326    ENDIF                          ! (fin debut)
327
328!
329! Appel a la routine sols continentaux
330!
331    IF (lafin) lrestart_write = .TRUE.
332    IF (check) WRITE(lunout,*)'lafin ',lafin,lrestart_write
333   
334    petA_orc(1:knon) = petBcoef(1:knon) * dtime
335    petB_orc(1:knon) = petAcoef(1:knon)
336    peqA_orc(1:knon) = peqBcoef(1:knon) * dtime
337    peqB_orc(1:knon) = peqAcoef(1:knon)
338
339    cdrag = 0.
340    cdrag(1:knon) = tq_cdrag(1:knon)
341
342! zlev(1:knon) = (100.*plev(1:knon))/((ps(1:knon)/287.05*temp_air(1:knon))*9.80665)
343    zlev(1:knon) = (100.*plev(1:knon))/((ps(1:knon)/RD*temp_air(1:knon))*RG)
344
345
346! PF et PASB
347!   where(cdrag > 0.01)
348!     cdrag = 0.01
349!   endwhere
350!  write(*,*)'Cdrag = ',minval(cdrag),maxval(cdrag)
351
352!
353! Init Orchidee
354!
355!  if (pole_nord) then
356!    offset=0
357!    ktindex(:)=ktindex(:)+iim-1
358!  else
359!    offset = klon_mpi_begin-1+iim-1
360!    ktindex(:)=ktindex(:)+MOD(offset,iim)
361!    offset=offset-MOD(offset,iim)
362!  endif
363 
364    IF (debut) THEN
365       CALL Get_orchidee_communicator(knon,orch_comm)
366       IF (knon /=0) THEN
367          CALL Init_orchidee_index(knon,orch_comm,knindex,offset,ktindex)
[802]368
[812]369#ifndef CPP_PARA
370#define ORC_PREPAR
371#endif
[799]372#ifdef ORC_PREPAR
[845]373          ! Interface for ORCHIDEE version 1.9 or earlier compiled in sequential mode(without preprocessing flag CPP_PARA)
[802]374          CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, knon, ktindex, dtime, &
375               lrestart_read, lrestart_write, lalo, &
376               contfrac, neighbours, resolution, date0, &
377               zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
378               cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
379               precip_rain, precip_snow, lwdown, swnet, swdown, ps, &
380               evap, fluxsens, fluxlat, coastalflow, riverflow, &
381               tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
382               lon_scat, lat_scat)
[799]383
384#else         
[845]385          ! Interface for ORCHIDEE version 1.9 compiled in parallel mode(with preprocessing flag CPP_PARA)
[781]386          CALL intersurf_main (itime+itau_phy-1, iim, jjm+1, offset, knon, ktindex, &
387               orch_comm, dtime, lrestart_read, lrestart_write, lalo, &
388               contfrac, neighbours, resolution, date0, &
389               zlev,  u1_lay(1:knon), v1_lay(1:knon), spechum(1:knon), temp_air(1:knon), epot_air(1:knon), ccanopy(1:knon), &
390               cdrag(1:knon), petA_orc(1:knon), peqA_orc(1:knon), petB_orc(1:knon), peqB_orc(1:knon), &
391               precip_rain(1:knon), precip_snow(1:knon), lwdown(1:knon), swnet(1:knon), swdown(1:knon), ps(1:knon), &
392               evap(1:knon), fluxsens(1:knon), fluxlat(1:knon), coastalflow(1:knon), riverflow(1:knon), &
393               tsol_rad(1:knon), tsurf_new(1:knon), qsurf(1:knon), albedo_out(1:knon,:), emis_new(1:knon), z0_new(1:knon), &
394               lon_scat, lat_scat)
[799]395#endif
[781]396         
397       ENDIF
398
399       albedo_keep(1:knon) = (albedo_out(1:knon,1)+albedo_out(1:knon,2))/2.
400
401    ENDIF
402
403!  swdown_vrai(1:knon) = swnet(1:knon)/(1. - albedo_keep(1:knon))
404    swdown_vrai(1:knon) = swdown(1:knon)
405
406    IF (knon /=0) THEN
407   
[799]408#ifdef ORC_PREPAR
[845]409       ! Interface for ORCHIDEE version 1.9 or earlier compiled in sequential mode(without preprocessing flag CPP_PARA)
410       CALL intersurf_main (itime+itau_phy, iim, jjm+1, knon, ktindex, dtime, &
[802]411            lrestart_read, lrestart_write, lalo, &
412            contfrac, neighbours, resolution, date0, &
413            zlev,  u1_lay, v1_lay, spechum, temp_air, epot_air, ccanopy, &
414            cdrag, petA_orc, peqA_orc, petB_orc, peqB_orc, &
[845]415            precip_rain, precip_snow, lwdown, swnet, swdown_vrai, ps, &
[802]416            evap, fluxsens, fluxlat, coastalflow, riverflow, &
417            tsol_rad, tsurf_new, qsurf, albedo_out, emis_new, z0_new, &
418            lon_scat, lat_scat)
419       
[799]420#else
[845]421       ! Interface for ORCHIDEE version 1.9 compiled in parallel mode(with preprocessing flag CPP_PARA)
[781]422       CALL intersurf_main (itime+itau_phy, iim, jjm+1,offset, knon, ktindex, &
423            orch_comm,dtime, lrestart_read, lrestart_write, lalo, &
424            contfrac, neighbours, resolution, date0, &
425            zlev,  u1_lay(1:knon), v1_lay(1:knon), spechum(1:knon), temp_air(1:knon), epot_air(1:knon), ccanopy(1:knon), &
426            cdrag(1:knon), petA_orc(1:knon), peqA_orc(1:knon), petB_orc(1:knon), peqB_orc(1:knon), &
427            precip_rain(1:knon), precip_snow(1:knon), lwdown(1:knon), swnet(1:knon), swdown_vrai(1:knon), ps(1:knon), &
428            evap(1:knon), fluxsens(1:knon), fluxlat(1:knon), coastalflow(1:knon), riverflow(1:knon), &
429            tsol_rad(1:knon), tsurf_new(1:knon), qsurf(1:knon), albedo_out(1:knon,:), emis_new(1:knon), z0_new(1:knon), &
430            lon_scat, lat_scat)
[799]431#endif
[781]432       
433    ENDIF
434
435    albedo_keep(1:knon) = (albedo_out(1:knon,1)+albedo_out(1:knon,2))/2.
436
437!* Send to coupler
438!
439    IF (ocean=='couple') THEN
440       CALL cpl_send_land_fields(itime, knon, knindex, &
441            riverflow, coastalflow)
442    ENDIF
443
444    alb_new(1:knon) = albedo_out(1:knon,1)
445    alblw(1:knon) = albedo_out(1:knon,2)
446
447! Convention orchidee: positif vers le haut
448    fluxsens(1:knon) = -1. * fluxsens(1:knon)
449    fluxlat(1:knon)  = -1. * fluxlat(1:knon)
450   
451!  evap     = -1. * evap
452
453    IF (debut) lrestart_read = .FALSE.
454   
455  END SUBROUTINE surf_land_orchidee
456!
457!****************************************************************************************
458!
459  SUBROUTINE Init_orchidee_index(knon,orch_comm,knindex,offset,ktindex)
460   
[793]461    INCLUDE "dimensions.h"
[781]462
463#ifdef CPP_PARA
464    INCLUDE 'mpif.h'
465#endif   
466
467
468! Input arguments
469!****************************************************************************************
470    INTEGER, INTENT(IN)                   :: knon
471    INTEGER, INTENT(IN)                   :: orch_comm
472    INTEGER, DIMENSION(klon), INTENT(IN)  :: knindex
473
474! Output arguments
475!****************************************************************************************
476    INTEGER, INTENT(OUT)                  :: offset
477    INTEGER, DIMENSION(knon), INTENT(OUT) :: ktindex
478
479! Local varables
480!****************************************************************************************
481#ifdef CPP_PARA
482    INTEGER, DIMENSION(MPI_STATUS_SIZE)   :: status
483#endif
484
485    INTEGER                               :: MyLastPoint
486    INTEGER                               :: LastPoint
[853]487    INTEGER                               :: mpi_rank_orch
488    INTEGER                               :: mpi_size_orch
489    INTEGER                               :: ierr
[802]490!
491! End definition
492!****************************************************************************************
493
[781]494    MyLastPoint=klon_mpi_begin-1+knindex(knon)+iim-1
495   
496    IF (is_parallel) THEN
497#ifdef CPP_PARA   
[853]498       CALL MPI_COMM_SIZE(orch_comm,mpi_size_orch,ierr)
499       CALL MPI_COMM_RANK(orch_comm,mpi_rank_orch,ierr)
[781]500#endif
501    ELSE
[853]502       mpi_rank_orch=0
503       mpi_size_orch=1
[781]504    ENDIF
[853]505
[781]506    IF (is_parallel) THEN
[853]507       IF (mpi_rank_orch /= 0) THEN
[781]508#ifdef CPP_PARA
[853]509          CALL MPI_RECV(LastPoint,1,MPI_INTEGER,mpi_rank_orch-1,1234,orch_comm,status,ierr)
[781]510#endif
511       ENDIF
512       
[853]513       IF (mpi_rank_orch /= mpi_size_orch-1) THEN
[781]514#ifdef CPP_PARA
[853]515          CALL MPI_SEND(MyLastPoint,1,MPI_INTEGER,mpi_rank_orch+1,1234,orch_comm,ierr) 
[781]516#endif
517       ENDIF
518    ENDIF
519   
[853]520    IF (mpi_rank_orch == 0) THEN
[781]521       offset=0
522    ELSE
523       offset=LastPoint-MOD(LastPoint,iim)
524    ENDIF
525   
526    ktindex(1:knon)=knindex(1:knon)+(klon_mpi_begin+iim-1)-offset-1     
527   
528
529  END SUBROUTINE  Init_orchidee_index
530!
531!****************************************************************************************
532!
533  SUBROUTINE Get_orchidee_communicator(knon,orch_comm)
534   
535#ifdef CPP_PARA
536    INCLUDE 'mpif.h'
537#endif   
538
539
540    INTEGER,INTENT(IN)  :: knon
541    INTEGER,INTENT(OUT) :: orch_comm
542   
543    INTEGER             :: color
544    INTEGER             :: ierr
[802]545!
546! End definition
547!****************************************************************************************
548
[781]549    IF (knon==0) THEN
550       color = 0
551    ELSE
552       color = 1
553    ENDIF
554   
555#ifdef CPP_PARA   
556    CALL MPI_COMM_SPLIT(COMM_LMDZ_PHY,color,mpi_rank,orch_comm,ierr)
557#endif
558   
559  END SUBROUTINE Get_orchidee_communicator
560!
561!****************************************************************************************
562
563  SUBROUTINE Init_neighbours(knon,neighbours,ktindex,pctsrf)
564   
565    INCLUDE "indicesol.h"
[793]566    INCLUDE "dimensions.h"
[781]567#ifdef CPP_PARA
568    INCLUDE 'mpif.h'
569#endif   
570
[802]571! Input arguments
572!****************************************************************************************
[781]573    INTEGER, INTENT(IN)                     :: knon
574    INTEGER, DIMENSION(klon), INTENT(IN)    :: ktindex
575    REAL, DIMENSION(klon), INTENT(IN)       :: pctsrf
576   
[802]577! Output arguments
578!****************************************************************************************
579    INTEGER, DIMENSION(knon,8), INTENT(OUT) :: neighbours
580
581! Local variables
582!****************************************************************************************
583    INTEGER                              :: knon_g
584    INTEGER                              :: i, igrid, jj, ij, iglob
585    INTEGER                              :: ierr, ireal, index
586    INTEGER, DIMENSION(0:mpi_size-1)     :: knon_nb
587    INTEGER, DIMENSION(0:mpi_size-1)     :: displs
588    INTEGER, DIMENSION(8,3)              :: off_ini
589    INTEGER, DIMENSION(8)                :: offset 
590    INTEGER, DIMENSION(knon)             :: ktindex_p
591    INTEGER, DIMENSION(iim,jjm+1)        :: correspond
592    INTEGER, ALLOCATABLE, DIMENSION(:)   :: ktindex_g
593    INTEGER, ALLOCATABLE, DIMENSION(:,:) :: neighbours_g
594    REAL, DIMENSION(klon_glo)            :: pctsrf_g
[781]595   
[802]596!
597! End definition
598!****************************************************************************************
599
[781]600    IF (is_sequential) THEN
601       knon_nb(:)=knon
602    ELSE 
603       
604#ifdef CPP_PARA 
605       CALL MPI_GATHER(knon,1,MPI_INTEGER,knon_nb,1,MPI_INTEGER,0,COMM_LMDZ_PHY,ierr)
606#endif
607       
608    ENDIF
609   
610    IF (is_mpi_root) THEN
611       knon_g=SUM(knon_nb(:))
612       ALLOCATE(ktindex_g(knon_g))
613       ALLOCATE(neighbours_g(knon_g,8))
614       neighbours_g(:,:)=-1
615       displs(0)=0
616       DO i=1,mpi_size-1
617          displs(i)=displs(i-1)+knon_nb(i-1)
618       ENDDO
619    ENDIF
620   
621    ktindex_p(1:knon)=ktindex(1:knon)+klon_mpi_begin-1+iim-1
622   
623    IF (is_sequential) THEN
624       ktindex_g(:)=ktindex_p(:)
625    ELSE
626       
627#ifdef CPP_PARA 
628       CALL MPI_GATHERV(ktindex_p,knon,MPI_INTEGER,ktindex_g,knon_nb,&
629            displs,MPI_INTEGER,0,COMM_LMDZ_PHY,ierr)
630#endif
631       
632    ENDIF
633   
634    CALL Gather(pctsrf,pctsrf_g)
635   
636    IF (is_mpi_root) THEN
637!  Initialisation des offset   
638!
639! offset bord ouest
640       off_ini(1,1) = - iim  ; off_ini(2,1) = - iim + 1; off_ini(3,1) = 1
641       off_ini(4,1) = iim + 1; off_ini(5,1) = iim      ; off_ini(6,1) = 2 * iim - 1
642       off_ini(7,1) = iim -1 ; off_ini(8,1) = - 1
643! offset point normal
644       off_ini(1,2) = - iim  ; off_ini(2,2) = - iim + 1; off_ini(3,2) = 1
645       off_ini(4,2) = iim + 1; off_ini(5,2) = iim      ; off_ini(6,2) = iim - 1
646       off_ini(7,2) = -1     ; off_ini(8,2) = - iim - 1
647! offset bord   est
648       off_ini(1,3) = - iim; off_ini(2,3) = - 2 * iim + 1; off_ini(3,3) = - iim + 1
649       off_ini(4,3) =  1   ; off_ini(5,3) = iim          ; off_ini(6,3) = iim - 1
650       off_ini(7,3) = -1   ; off_ini(8,3) = - iim - 1
651!
652!
653! Attention aux poles
654!
655       DO igrid = 1, knon_g
656          index = ktindex_g(igrid)
657          jj = INT((index - 1)/iim) + 1
658          ij = index - (jj - 1) * iim
659          correspond(ij,jj) = igrid
660       ENDDO
661       
662       DO igrid = 1, knon_g
663          iglob = ktindex_g(igrid)
664          IF (MOD(iglob, iim) == 1) THEN
665             offset = off_ini(:,1)
666          ELSE IF(MOD(iglob, iim) == 0) THEN
667             offset = off_ini(:,3)
668          ELSE
669             offset = off_ini(:,2)
670          ENDIF
671          DO i = 1, 8
672             index = iglob + offset(i)
673             ireal = (MIN(MAX(1, index - iim + 1), klon_glo))
674             IF (pctsrf_g(ireal) > EPSFRA) THEN
675                jj = INT((index - 1)/iim) + 1
676                ij = index - (jj - 1) * iim
677                neighbours_g(igrid, i) = correspond(ij, jj)
678             ENDIF
679          ENDDO
680       ENDDO
681
682    ENDIF
683   
684    DO i=1,8
685       IF (is_sequential) THEN
686          neighbours(:,i)=neighbours_g(:,i)
687       ELSE
688#ifdef CPP_PARA
689          CALL MPI_SCATTERV(neighbours_g(:,i),knon_nb,displs,MPI_INTEGER,neighbours(:,i),knon,MPI_INTEGER,0,COMM_LMDZ_PHY,ierr)
690#endif
691       ENDIF
692    ENDDO
693   
694  END SUBROUTINE Init_neighbours
695!
696!****************************************************************************************
697!
698
699#endif
700
701END MODULE surf_land_orchidee_mod
Note: See TracBrowser for help on using the repository browser.