SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
interpol_field2d.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 interpol_field2d (UG, U, &
7  hprogram,kluout,kcode,pfield,hfield,pdef,knpts)
8 ! ################################################
9 !
10 !!**** *INTERPOL_FIELD* initializes coordinate system for spline interpolation
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !! The points are all on only one grid (defined with the coordinates
16 !! of all the points). The code to apply for each point is:
17 !!
18 !! KCODE>0 : data point (with field valid for interpolation)
19 !! KCODE=-1: point to ignore
20 !! KCODE=0 : point to interpolate
21 !!
22 !!
23 !!
24 !! AUTHOR
25 !! ------
26 !!
27 !! V. Masson Meteo-France
28 !!
29 !! MODIFICATION
30 !! ------------
31 !!
32 !! Original 01/2004
33 !! Modification
34 !! A. Alias 07/2013 add MODI_ABOR1_SFX
35 !----------------------------------------------------------------------------
36 !
37 !* 0. DECLARATION
38 ! -----------
39 !
40 !
41 !
43 USE modd_surf_atm_n, ONLY : surf_atm_t
44 !
45 USE modd_surf_par, ONLY : xundef
46 !
47 USE modi_get_grid_coord
48 USE modi_interpol_npts
49 USE modi_sum_on_all_procs
50 USE modi_abor1_sfx
51 !
52 USE yomhook ,ONLY : lhook, dr_hook
53 USE parkind1 ,ONLY : jprb
54 !
55 IMPLICIT NONE
56 !
57 !* 0.1 Declaration of arguments
58 ! ------------------------
59 !
60 !
61 TYPE(surf_atm_grid_t), INTENT(INOUT) :: ug
62 TYPE(surf_atm_t), INTENT(INOUT) :: u
63 !
64  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! host program
65 INTEGER, INTENT(IN) :: kluout ! output listing
66 INTEGER,DIMENSION(:), INTENT(INOUT) :: kcode ! code for each point
67  ! >0 point used for interpolation
68  ! 0 point to interpolate
69  ! -1 point not used
70  ! -2 point not used
71 ! ! -3 if spline is no computed
72 ! ! for this point
73 REAL, DIMENSION(:,:),INTENT(INOUT) :: pfield ! pgd field on grid mesh.
74  CHARACTER(LEN=*), INTENT(IN) :: hfield ! name of the field for prints
75 REAL,DIMENSION(:),OPTIONAL, INTENT(IN):: pdef ! default value if not enough data
76 INTEGER, OPTIONAL, INTENT(IN) :: knpts ! number of points to interpolate with
77 
78 !
79 !* 0.2 Declaration of local variables
80 ! ------------------------------
81 !
82 REAL, DIMENSION(SIZE(KCODE)) :: zx ! coordinate used for
83 REAL, DIMENSION(SIZE(KCODE)) :: zy ! splines interpolation
84 REAL, DIMENSION(SIZE(PFIELD,2)):: zdef ! default value for field
85 INTEGER :: inpts ! number of points to interpolate with
86 INTEGER :: ihalo, inear_nbr
87 
88 !
89 INTEGER :: jloop ! loop counter
90 !
91 INTEGER :: ierr0
92 INTEGER :: ierr1 ! number of points interpolated
93 INTEGER :: ierr2 ! number of points not interpolated in the end
94 !
95 REAL(KIND=JPRB) :: zhook_handle
96 !-------------------------------------------------------------------------------
97 !
98 IF (lhook) CALL dr_hook('INTERPOL_FIELD:INTERPOL_FIELD2D',0,zhook_handle)
99 !
100 inpts = 3
101 IF (present(knpts)) inpts = knpts
102 !
103 zdef = xundef
104 IF (present(pdef)) zdef = pdef
105 !
106 !* 2. Miscellaneous Initializations
107 ! -----------------------------
108 !
109  CALL get_grid_coord(ug, u, &
110  kluout,px=zx,py=zy)
111 !
112 !-------------------------------------------------------------------------------
113 !
114 !* 5. Interpolation with 3 nearest points
115 ! -----------------------------------
116 !
117 ierr0 = sum_on_all_procs(hprogram,ug%CGRID,kcode(:)==0)
118 !
119  CALL get_interp_halo(hprogram,ug%CGRID,ihalo)
120 !
121 IF (ihalo/=0) THEN
122  inear_nbr = (2*ihalo+1)**2
123 ELSE
124  inear_nbr = u%NDIM_FULL
125 ENDIF
126 !
127  CALL interpol_npts(ug, u, &
128  hprogram,kluout,inpts,kcode,zx,zy,pfield,inear_nbr)
129 !
130 !-------------------------------------------------------------------------------
131 !
132 !* 6. Final check
133 ! -----------
134 !
135 ierr1 = sum_on_all_procs(hprogram,ug%CGRID,kcode(:)==0)
136 ierr2 = sum_on_all_procs(hprogram,ug%CGRID,kcode(:)==-4)
137 !
138 IF (ierr1>0 .OR. ierr2>0) THEN
139  !
140  WRITE(kluout,*) ' '
141  WRITE(kluout,*) ' Interpolation of field : ',hfield
142  WRITE(kluout,*) ' ----------------------'
143  WRITE(kluout,*) ' '
144  WRITE(kluout,*) ' Number of points interpolated with ',inpts,' nearest points: ', &
145  ierr1
146  !
147  !
148  IF (ierr2>0) THEN
149  WRITE(kluout,*) ' Number of points that could not be interpolated : ', &
150  ierr2
151  IF (present(pdef) .AND. (inear_nbr>=u%NDIM_FULL .OR. ierr2==ierr0)) THEN
152  DO jloop=1,SIZE(pfield,2)
153  WRITE(kluout,*) ' For these points, the default value (',zdef(jloop),') is set.'
154  ENDDO
155  ELSE
156  WRITE(kluout,*) ' Please provide data with better resolution'
157  WRITE(kluout,*) ' Or define a higher halo value '
158  END IF
159  END IF
160 !
161 END IF
162 !
163 IF (ierr2>0) THEN
164  !
165  IF (.NOT.present(pdef) .OR. (inear_nbr<u%NDIM_FULL .AND. ierr2/=ierr0)) &
166  CALL abor1_sfx('Some points lack data and are too far away from other points. &
167  Please define a higher halo value in NAM_IO_OFFLINE.')
168  !
169 ENDIF
170 !
171 IF (count(kcode(:)==-4)>0) THEN
172  !
173  DO jloop=1,SIZE(pfield,2)
174  IF (zdef(jloop)/=xundef) THEN
175  WHERE(kcode(:)==-4)
176  pfield(:,jloop)=zdef(jloop)
177  END WHERE
178  ENDIF
179  END DO
180  !
181 END IF
182 !
183 IF (lhook) CALL dr_hook('INTERPOL_FIELD:INTERPOL_FIELD2D',1,zhook_handle)
184 !-------------------------------------------------------------------------------
185 !
186 END SUBROUTINE interpol_field2d
subroutine get_grid_coord(UG, U, KLUOUT, PX, PY, KL, HGRID, PGRID_PAR)
integer function sum_on_all_procs(HPROGRAM, HGRID, OIN, HNAME)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine interpol_field2d(UG, U, HPROGRAM, KLUOUT, KCODE, PFIELD, HFIELD, PDEF, KNPTS)
subroutine interpol_npts(UG, U, HPROGRAM, KLUOUT, KNPTS, KCODE, PX, PY, PFIELD, KNEAR_NBR)
subroutine get_interp_halo(HPROGRAM, HGRID, KHALO)