SURFEX v8.1
General documentation of Surfex
bilin_extrap.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_extrap (KLUOUT,KX,KY,KCIJ,PX1,PY1,PFIELD1,PX2,PY2,PFIELD2,OINTERP)
7 ! #########################################################################
8 !
9 !!**** *BILIN_EXTRAPEAR * - 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 !
87 USE modi_hor_extrapol_surf
88 !
89 USE modd_surf_par, ONLY : xundef
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 INTEGER, DIMENSION(:,:), INTENT(IN) :: KCIJ
105 REAL, DIMENSION(:), INTENT(IN) :: PX1 ! X coordinate of the regular input grid
106 REAL, DIMENSION(:), INTENT(IN) :: PY1 ! Y coordinate of the regular input grid
107 REAL, DIMENSION(:,:), INTENT(IN) :: PFIELD1 ! FIELD on regular input grid
108 REAL, DIMENSION(:), INTENT(IN) :: PX2 ! X coordinate of all points of output grid
109 REAL, DIMENSION(:), INTENT(IN) :: PY2 ! Y coordinate of all points of output grid
110 REAL, DIMENSION(:,:), INTENT(INOUT) :: PFIELD2 ! FIELD on model 2
111 LOGICAL, DIMENSION(:),INTENT(IN) :: OINTERP ! .true. where physical value is needed
112 !
113 !
114 !* 0.2 Declarations of local variables for print on FM file
115 !
116 INTEGER, DIMENSION(:,:), ALLOCATABLE :: IP
117 INTEGER, DIMENSION(KY) :: IX
118 ! Variables implied in the extension procedure
119 INTEGER :: ICOUNT
120  ! Loop counters
121 INTEGER :: INFOMPI, JL, JI, INL, INO
122 REAL(KIND=JPRB) :: ZHOOK_HANDLE, ZHOOK_HANDLE_OMP
123 !-------------------------------------------------------------------------------
124 !
125 IF (lhook) CALL dr_hook('BILIN_EXTRAP',0,zhook_handle)
126 !
127 ino = SIZE(pfield2,1)
128 inl = SIZE(pfield2,2)
129 !
130 !* 6. EXTRAPOLATIONS IF SOME POINTS WERE NOT INTERPOLATED
131 ! ---------------------------------------------------
132 !
133 !* no data point
134 IF (nrank==npio) icount = count(pfield1(:,:)/=xundef)
135 IF (nproc>1) THEN
136 #ifdef SFX_MPI
137  CALL mpi_bcast(icount,kind(icount)/4,mpi_integer,npio,ncomm,infompi)
138 #endif
139 ENDIF
140 IF (icount==0 .AND. lhook) CALL dr_hook('BILIN_EXTRAP',1,zhook_handle)
141 IF (icount==0) RETURN
142 !
143 DO jl=1,inl
144  WRITE(kluout,*) ' Remaining horizontal extrapolations'
145  WRITE(kluout,*) ' Total number of input data : ',icount,' / ',SIZE(pfield2(:,jl))
146  WRITE(kluout,*) ' Number of points to interpolate: ',count(pfield2(:,jl)==xundef .AND. ointerp(:))
147 ENDDO
148 !
149 ALLOCATE(ip(ino,1))
150 DO ji=1,ino
151  ip(ji,1) = kx*(kcij(ji,2)-1)+kcij(ji,1)
152 ENDDO
153 !* input grid coordinates
154 !
155 ix(:) = kx
156  CALL hor_extrapol_surf(kluout,'XY ',kx*ky,py1(1),py1(ky),px1(1),px1(kx),ky,ix,&
157  ip,pfield1,py2,px2,pfield2,ointerp)
158 !
159 DEALLOCATE(ip)
160 !
161 IF (lhook) CALL dr_hook('BILIN_EXTRAP',1,zhook_handle)
162 !-------------------------------------------------------------------------------
163 !
164 END SUBROUTINE bilin_extrap
subroutine hor_extrapol_surf(KLUOUT, HCOORTYPE, KILEN, PILA1, PILA2, PI
real, parameter xundef
integer, parameter jprb
Definition: parkind1.F90:32
logical lhook
Definition: yomhook.F90:15
subroutine bilin_extrap(KLUOUT, KX, KY, KCIJ, PX1, PY1, PFIELD1, PX2, PY2, PFIELD2, OINTERP)
Definition: bilin_extrap.F90:7
static int count
Definition: memory_hook.c:21