source: LMDZ4/trunk/libf/phylmd/surf_land_orchidee_mod.F90 @ 802

Last change on this file since 802 was 802, checked in by Laurent Fairhead, 17 years ago

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