SURFEX v8.1
General documentation of Surfex
bilin_value.F90
Go to the documentation of this file.
1 !SFX_LIC Copyright 1994-2014 CNRS, Meteo-France and Universite Paul Sabatier
2 !SFX_LIC This is part of the SURFEX software governed by the CeCILL-C licence
3 !SFX_LIC version 1. See LICENSE, CeCILL-C_V1-en.txt and CeCILL-C_V1-fr.txt
4 !SFX_LIC for details. version 1.
5 ! #########
6  SUBROUTINE bilin_value (KLUOUT,KX,KY,PFIELD1,PCX,PCY,KCI,KCJ,PFIELD2)
7 ! #########################################################################
8 !
9 !!**** *BILIN_VALUEEAR * - subroutine to interpolate surface FIELD
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !! Interpolation is bilinear, and uses 9 grid points, located in the
19 !! center of model 1 grid mesh, and at the boundaries of this grid
20 !! mesh (2 X limits, 2 Y limits and 4 corners).
21 !! This implies that the grid mesh values located around the model 1
22 !! grid mesh are not used directly. The values at the boundaries of the
23 !! grid mesh are defined by the average between the middle point
24 !! (this grid mesh value), and the one in the considered direction.
25 !! So the eight grid meshes around the considered grid mesh are used
26 !! equally.
27 !! This is important to note that these average values are erased
28 !! and replaced by zero if they are at the limit of any grid
29 !! mesh with the zero value. This allows to insure zero value in model 2
30 !! grid meshes where there was not the considered class in corresponding
31 !! model 1 grid mesh, and to insure continuity of the FIELD type
32 !! at such boundaries.
33 !!
34 !!
35 !! The arrays and array index are defined on the following (model1) grid:
36 !!
37 !!
38 !! XFIELD XFIELD XFIELD
39 !! * * *
40 !! i-1,j+1 i,j+1 i+1,j+1
41 !!
42 !!
43 !!
44 !! ZFIELD_XY ZFIELD_Y ZFIELD_XY
45 !! * * *
46 !! i,j+1 i,j+1 i+1,j+1
47 !!
48 !!
49 !!
50 !! XFIELD ZFIELD_X XFIELD ZFIELD_X XFIELD
51 !! * * * * *
52 !! i-1,j i,j i,j i+1,j i+1,j
53 !!
54 !!
55 !!
56 !! ZFIELD_XY ZFIELD_Y ZFIELD_XY
57 !! * * *
58 !! i,j i,j i+1,j
59 !!
60 !!
61 !!
62 !! XFIELD XFIELD XFIELD
63 !! * * *
64 !! i-1,j-1 i,j-1 i+1,j-1
65 !!
66 !!
67 !!
68 !!
69 !!
70 !! AUTHOR
71 !! ------
72 !!
73 !! V. Masson * METEO-FRANCE *
74 !!
75 !! MODIFICATIONS
76 !! -------------
77 !!
78 !! Original 01/2004
79 ! TD&DD: added OpenMP directives
80 
81 !-------------------------------------------------------------------------------
82 !
83 !* 0. DECLARATIONS
84 ! ------------
85 !
86 USE modd_surfex_mpi, ONLY : nrank, npio, ncomm, nproc, idx_i
87 USE modd_surf_par, ONLY : xundef
88 !
89 USE modi_bilin_gridin
90 !
91 USE yomhook ,ONLY : lhook, dr_hook
92 USE parkind1 ,ONLY : jprb
93 !
94 IMPLICIT NONE
95 !
96 #ifdef SFX_MPI
97 include "mpif.h"
98 #endif
99 !
100 !* 0.1 Declarations of dummy arguments :
101 !
102 INTEGER, INTENT(IN) :: KLUOUT ! output listing logical unit
103 INTEGER, INTENT(IN) :: KX, KY
104 REAL, DIMENSION(:,:), INTENT(IN) :: PFIELD1 ! FIELD on regular input grid
105 REAL, DIMENSION(:,:), INTENT(IN) :: PCX, PCY
106 INTEGER, DIMENSION(:), INTENT(IN):: KCI, KCJ
107 REAL, DIMENSION(:,:), INTENT(OUT) :: PFIELD2 ! FIELD on model 2
108 !
109 !* 0.2 Declarations of local variables for print on FM file
110 !
111 #ifdef SFX_MPI
112 INTEGER, DIMENSION(MPI_STATUS_SIZE) :: ISTATUS
113 #endif
114 REAL, DIMENSION(:,:,:), ALLOCATABLE :: ZFIELD1,ZFIELDS
115 REAL, DIMENSION(:,:), ALLOCATABLE :: ZFIELD_X, ZFIELD_Y, ZFIELD_XY
116 INTEGER, DIMENSION(2) :: IB
117 INTEGER, DIMENSION(2,2) :: IJEXT
118 INTEGER, DIMENSION(2,2,0:NPROC-1) :: IBOR
119 INTEGER :: INFOMPI, ISIZE, IS1, IS2, J, IT1, IT2
120 INTEGER :: JL, JK, JI, JJ, INL ! grid 2 index
121 !
122 REAL(KIND=JPRB) :: ZHOOK_HANDLE, ZHOOK_HANDLE_OMP
123 !-------------------------------------------------------------------------------
124 !
125 IF (lhook) CALL dr_hook('BILIN_VALUE_1',0,zhook_handle)
126 !
127 inl = SIZE(pfield2,2)
128 !
129 IF (SIZE(kci)>0) THEN
130  ijext(1,1) = max(1,minval(kci)-1)
131  ijext(1,2) = min(maxval(kci)+1,kx)
132  ijext(2,1) = max(1,minval(kcj)-1)
133  ijext(2,2) = min(maxval(kcj)+1,ky)
134 ELSE
135  ijext(:,:) = 0
136 ENDIF
137 !
138 IF (lhook) CALL dr_hook('BILIN_VALUE_1',1,zhook_handle)
139 
140 IF (lhook) CALL dr_hook('BILIN_VALUE_2',0,zhook_handle)
141 !
142 IF (nproc>1) THEN
143 #ifdef SFX_MPI
144  CALL mpi_gather(ijext,4*kind(ijext)/4,mpi_integer,&
145  ibor,4*kind(ibor)/4,mpi_integer,&
146  npio,ncomm,infompi)
147 #endif
148 ELSE
149  ibor(:,:,0) = ijext(:,:)
150 ENDIF
151 !
152 IF (lhook) CALL dr_hook('BILIN_VALUE_2',1,zhook_handle)
153 !
154 IF (nrank/=npio) THEN
155  !
156  IF (lhook) CALL dr_hook('BILIN_VALUE_3',0,zhook_handle)
157  !
158  idx_i = idx_i + 1
159  is1 = ijext(1,2)-ijext(1,1)+1
160  is2 = ijext(2,2)-ijext(2,1)+1
161  isize = is1*is2
162  ALLOCATE(zfield1(is1,is2,inl))
163 #ifdef SFX_MPI
164  IF (sum(ijext)/=0) &
165  CALL mpi_recv(zfield1,isize*inl*kind(zfield1)/4,mpi_real,npio,idx_i,ncomm,istatus,infompi)
166 #endif
167  !
168  IF (lhook) CALL dr_hook('BILIN_VALUE_3',1,zhook_handle)
169  !
170 ELSE
171  !
172 !$OMP PARALLEL PRIVATE(ZHOOK_HANDLE_OMP)
173 !$OMP DO SCHEDULE(DYNAMIC,1) PRIVATE(J,IT1,IT2,ISIZE,ZFIELDS)
174  DO j=0,nproc-1
175  !
176  IF (j/=npio) THEN
177  !
178  IF (lhook) CALL dr_hook('BILIN_VALUE_31',0,zhook_handle_omp)
179  !
180  it1 = ibor(1,2,j)-ibor(1,1,j)+1
181  it2 = ibor(2,2,j)-ibor(2,1,j)+1
182  isize = it1*it2
183  IF (sum(ibor(:,:,j))/=0) THEN
184  ALLOCATE(zfields(it1,it2,inl))
185  DO jl=ibor(2,1,j),ibor(2,2,j)
186  zfields(:,jl-ibor(2,1,j)+1,:) = pfield1(kx*(jl-1)+ibor(1,1,j):kx*(jl-1)+ibor(1,2,j),:)
187  ENDDO
188 #ifdef SFX_MPI
189  CALL mpi_send(zfields,SIZE(zfields)*kind(zfields)/4,mpi_real,j,idx_i+1,ncomm,infompi)
190 #endif
191  DEALLOCATE(zfields)
192  ENDIF
193  IF (lhook) CALL dr_hook('BILIN_VALUE_31',1,zhook_handle_omp)
194  !
195  ELSE
196  !
197  IF (lhook) CALL dr_hook('BILIN_VALUE_32',0,zhook_handle_omp)
198  !
199  is1 = ibor(1,2,0)-ibor(1,1,0)+1
200  is2 = ibor(2,2,0)-ibor(2,1,0)+1
201  isize = is1*is2
202  ALLOCATE(zfield1(is1,is2,inl))
203  IF (sum(ibor(:,:,0))/=0) THEN
204  DO jl=ibor(2,1,0),ibor(2,2,0)
205  zfield1(:,jl-ibor(2,1,0)+1,:) = pfield1(kx*(jl-1)+ibor(1,1,0):kx*(jl-1)+ibor(1,2,0),:)
206  ENDDO
207  ENDIF
208  !
209  IF (lhook) CALL dr_hook('BILIN_VALUE_32',1,zhook_handle_omp)
210  !
211  ENDIF
212  !
213  ENDDO
214 !$OMP END DO
215 !$OMP END PARALLEL
216  !
217  idx_i = idx_i + 1
218  !
219 ENDIF
220 !
221 ALLOCATE(zfield_x(is1+1,is2),zfield_y(is1,is2+1),zfield_xy(is1+1,is2+1))
222 !
223 DO jk=1,inl
224  !
225  IF (lhook) CALL dr_hook('BILIN_VALUE_4',0,zhook_handle)
226  CALL bilin_gridin(zfield1(:,:,jk),zfield_x,zfield_y,zfield_xy)
227  !
228  IF (lhook) CALL dr_hook('BILIN_VALUE_4',1,zhook_handle)
229  IF (lhook) CALL dr_hook('BILIN_VALUE_5',0,zhook_handle)
230  pfield2(:,jk) = xundef
231  !
232  DO jl=1,SIZE(pfield2,1)
233  !
234  ji = kci(jl) - ijext(1,1) + 1
235  jj = kcj(jl) - ijext(2,1) + 1
236  ji = max(min(ji,SIZE(zfield1,1)),0)
237  jj = max(min(jj,SIZE(zfield1,2)),0)
238  !
239  !* interpolation weights in X direction
240  !
241  !
242  !* interpolation
243  !
244  IF(zfield1(ji,jj,jk) /= xundef) THEN
245 
246  pfield2(jl,jk) = pcy(jl,1) * &
247  ( pcx(jl,1) * zfield_xy(ji,jj) + pcx(jl,2) * zfield_y(ji,jj) + pcx(jl,3) * zfield_xy(ji+1,jj) ) &
248  + pcy(jl,2) * &
249  ( pcx(jl,1) * zfield_x(ji,jj) + pcx(jl,2) * zfield1(ji,jj,jk) + pcx(jl,3) * zfield_x(ji+1,jj) ) &
250  + pcy(jl,3) * &
251  ( pcx(jl,1) * zfield_xy(ji,jj+1) + pcx(jl,2) * zfield_y(ji,jj+1) + pcx(jl,3) * zfield_xy(ji+1,jj+1) )
252 
253  ENDIF
254 
255  END DO
256  !
257  IF (lhook) CALL dr_hook('BILIN_VALUE_5',1,zhook_handle)
258  !
259 ENDDO
260 !
261 IF (lhook) CALL dr_hook('BILIN_VALUE_6',0,zhook_handle)
262 !
263 DEALLOCATE(zfield1,zfield_x,zfield_y,zfield_xy)
264 !
265 !-------------------------------------------------------------------------------
266 !
267 WHERE(abs(pfield2-xundef)<1.e-6) pfield2=xundef
268 !
269 IF (lhook) CALL dr_hook('BILIN_VALUE_6',1,zhook_handle)
270 !-------------------------------------------------------------------------------
271 !
272 END SUBROUTINE bilin_value
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
subroutine bilin_gridin(PFIELD1, PFIELD_X, PFIELD_Y, PFIELD_XY)
Definition: bilin_gridin.F90:7
intent(out) overrides sub arrays one Sort by the least significant key first sum(iindex(1:n))
logical lhook
Definition: yomhook.F90:15
subroutine bilin_value(KLUOUT, KX, KY, PFIELD1, PCX, PCY, KCI, KCJ, PFIELD2)
Definition: bilin_value.F90:7