source: trunk/LMDZ.PLUTO/libf/muphypluto/lint_gen.F90 @ 3590

Last change on this file since 3590 was 3560, checked in by debatzbr, 7 weeks ago

Addition of the microphysics model in moments.

File size: 46.1 KB
Line 
1! Copyright (c) Université de Reims Champagnne-Ardenne (2010-2015)
2! Contributor: Jérémie Burgalat (jeremie.burgalat@univ-reims.fr)
3!
4! This software is a computer program whose purpose is to compute multi-variate
5! linear interpolation.
6!
7! This software is governed by the CeCILL-B license under French law and
8! abiding by the rules of distribution of free software.  You can  use,
9! modify and/ or redistribute the software under the terms of the CeCILL-B
10! license as circulated by CEA, CNRS and INRIA at the following URL
11! "http://www.cecill.info".
12!
13! As a counterpart to the access to the source code and  rights to copy,
14! modify and redistribute granted by the license, users are provided only
15! with a limited warranty  and the software's author,  the holder of the
16! economic rights,  and the successive licensors  have only  limited
17! liability.
18!
19! In this respect, the user's attention is drawn to the risks associated
20! with loading,  using,  modifying and/or developing or reproducing the
21! software by the user in light of its specific status of free software,
22! that may mean  that it is complicated to manipulate,  and  that  also
23! therefore means  that it is reserved for developers  and  experienced
24! professionals having in-depth computer knowledge. Users are therefore
25! encouraged to load and test the software's suitability as regards their
26! requirements in conditions enabling the security of their systems and/or
27! data to be ensured and,  more generally, to use and operate it in the
28! same conditions as regards security.
29!
30! The fact that you are presently reading this means that you have had
31! knowledge of the CeCILL-B license and that you accept its terms.
32
33!! File:    lint_gen.F90
34!! Summary: Linear interpolation generic interfaces
35!! Author:  J. Burgalat
36!! Date:    2010-2014
37
38MODULE LINT_GEN
39    !! Generic linear interpolation module
40    USE LINT_PREC
41    USE LINT_CORE
42    IMPLICIT NONE
43 
44    PUBLIC  :: lintgen, hdcd_lint_gen
45    PRIVATE
46 
47    !> Interface to multi-variate linear interpolation
48    !!
49    !! For __n__, the number of function's variables, user must provide:
50    !!
51    !! - __n__ scalar(s) with the coordinate(s) of the point to interpolate.
52    !! - __n__ vector(s) with the tabulated values of each coordinate.
53    !! - a single __n__-D array with the value of tabulated function at each
54    !!   tabulated coordinate.
55    !! - A function, satisfying [[lintcore(module):locate(interface)]] interface,
56    !!   that locates the neighbourhood of the point to interpolate.
57    !! - A scalar that stores the output value.
58    INTERFACE lintgen
59      MODULE PROCEDURE l1d_gen_sc,l2d_gen_sc,l3d_gen_sc,l4d_gen_sc,l5d_gen_sc
60      MODULE PROCEDURE l1d_gen_ve,l2d_gen_ve,l3d_gen_ve,l4d_gen_ve,l5d_gen_ve
61    END INTERFACE
62 
63    !> Interface to multi-variate hard-coded linear interpolation
64    !!
65    !! Same remarks as in [[lint_gen(module):lintgen(interface)]] apply here.
66    INTERFACE hdcd_lint_gen
67      MODULE PROCEDURE hdcdl1d_gen_sc, hdcdl2d_gen_sc, hdcdl3d_gen_sc, &
68                       hdcdl4d_gen_sc, hdcdl5d_gen_sc
69      MODULE PROCEDURE hdcdl1d_gen_ve, hdcdl2d_gen_ve, hdcdl3d_gen_ve, &
70                       hdcdl4d_gen_ve, hdcdl5d_gen_ve
71    END INTERFACE
72 
73    CONTAINS
74 
75    ! GENERIC versions
76    ! ----------------
77 
78    FUNCTION l1d_gen_sc(x,cx,cv, locator,res) RESULT(ret)
79      !! Wrapper interface for 1D linear interpolation (scalar)
80      !!
81      !! @warning
82      !! On error, __res__ output value is undefined.
83      REAL(kind=wp), INTENT(in)               :: x       !! X coordinate of the point to interpolate
84      REAL(kind=wp), INTENT(in), DIMENSION(:) :: cx      !! Tabulated function X coordinates
85      REAL(kind=wp), INTENT(in), DIMENSION(:) :: cv      !! Tabulated function values
86      REAL(kind=wp), INTENT(out)              :: res     !! Interpolated value
87      PROCEDURE(locate)                       :: locator !! Locator function
88      LOGICAL :: ret                                     !! .true. on success, .false. otherwise
89      REAL(kind=wp), DIMENSION(2,2) :: g1d
90      INTEGER                       :: i,ix
91      ret = .false.
92      ix = locator(x,cx) ; IF (ix == 0) RETURN
93      DO i=0,1
94        g1d(i+1,1) = cx(ix+i)
95        g1d(i+1,2) = cv(ix+i)
96      ENDDO
97      res = lintc_((/x/),g1d)
98      ret = .true.
99    END FUNCTION l1d_gen_sc
100 
101    FUNCTION l2d_gen_sc(x,y,cx,cy,cv,locator,res) RESULT(ret)
102      !! Wrapper interface for 2D linear interpolation (scalar)
103      !!
104      !! @warning
105      !! On error, __res__ output value is undefined.
106      REAL(kind=wp), INTENT(in)                 :: x       !! X coordinate of the point to interpolate
107      REAL(kind=wp), INTENT(in)                 :: y       !! Y coordinate of the point to interpolate
108      REAL(kind=wp), INTENT(in), DIMENSION(:)   :: cx      !! Tabulated function X coordinates
109      REAL(kind=wp), INTENT(in), DIMENSION(:)   :: cy      !! Tabulated function Y coordinates
110      REAL(kind=wp), INTENT(in), DIMENSION(:,:) :: cv      !! Tabulated function values
111      REAL(kind=wp), INTENT(out)                :: res     !! Interpolated value
112      PROCEDURE(locate)                         :: locator !! Locator function
113      LOGICAL :: ret                                       !! .true. on success, .false. otherwise
114      REAL(kind=wp), DIMENSION(4,3) :: g2d
115      INTEGER                       :: ix0,iy0,i,a,b
116      ret = .false.
117      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
118      iy0 = locator(y,cy) ; IF (iy0 == 0) RETURN
119      DO i=1,4
120        a=ix0+MOD((i-1),2)   ; g2d(i,1) = cx(a)
121        b=iy0+MOD((i-1)/2,2) ; g2d(i,2) = cy(b)
122        g2d(i,3) = cv(a,b)
123      ENDDO
124      res = lintc_((/x,y/),g2d)
125      ret = .true.
126    END FUNCTION l2d_gen_sc
127 
128    FUNCTION l3d_gen_sc(x,y,z,cx,cy,cz,cv,locator,res) RESULT(ret)
129      !! Wrapper interface for 3D linear interpolation (scalar)
130      !!
131      !! @warning
132      !! On error, __res__ output value is undefined.
133      REAL(kind=wp), INTENT(in)                   :: x       !! X coordinate of the point to interpolate
134      REAL(kind=wp), INTENT(in)                   :: y       !! Y coordinate of the point to interpolate
135      REAL(kind=wp), INTENT(in)                   :: z       !! Z coordinate of the point to interpolate
136      REAL(kind=wp), INTENT(in), DIMENSION(:)     :: cx      !! Tabulated function X coordinates
137      REAL(kind=wp), INTENT(in), DIMENSION(:)     :: cy      !! Tabulated function Y coordinates
138      REAL(kind=wp), INTENT(in), DIMENSION(:)     :: cz      !! Tabulated function Z coordinates
139      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:) :: cv      !! Tabulated function values
140      REAL(kind=wp), INTENT(out)                  :: res     !! Interpolated value
141      PROCEDURE(locate)                           :: locator !! Locator function
142      LOGICAL :: ret                                         !! .true. on success, .false. otherwise
143      REAL(kind=wp), DIMENSION(8,4) :: g3d
144      INTEGER                      :: ix0,iy0,iz0,i,a,b,c
145      ret = .false.
146      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
147      iy0 = locator(y,cy) ; IF (iy0 == 0) RETURN
148      iz0 = locator(z,cz) ; IF (iz0 == 0) RETURN
149      DO i=1,8
150        a=ix0+MOD((i-1),2)   ; g3d(i,1) = cx(a)
151        b=iy0+MOD((i-1)/2,2) ; g3d(i,2) = cy(b)
152        c=iz0+MOD((i-1)/4,2) ; g3d(i,3) = cz(c)
153        g3d(i,4) = cv(a,b,c)
154      ENDDO
155      res = lintc_((/x,y,z/),g3d)
156      ret = .true.
157    END FUNCTION l3d_gen_sc
158 
159    FUNCTION l4d_gen_sc(x,y,z,t,cx,cy,cz,ct,cv,locator,res) RESULT(ret)
160      !! Wrapper interface for 4D linear interpolation (scalar)
161      !!
162      !! @warning
163      !! On error, __res__ output value is undefined.
164      REAL(kind=wp), INTENT(in)                     :: x       !! X coordinate of the point to interpolate
165      REAL(kind=wp), INTENT(in)                     :: y       !! Y coordinate of the point to interpolate
166      REAL(kind=wp), INTENT(in)                     :: z       !! Z coordinate of the point to interpolate
167      REAL(kind=wp), INTENT(in)                     :: t       !! T coordinate of the point to interpolate
168      REAL(kind=wp), INTENT(in), DIMENSION(:)       :: cx      !! Tabulated function X coordinates
169      REAL(kind=wp), INTENT(in), DIMENSION(:)       :: cy      !! Tabulated function Y coordinates
170      REAL(kind=wp), INTENT(in), DIMENSION(:)       :: cz      !! Tabulated function Z coordinates
171      REAL(kind=wp), INTENT(in), DIMENSION(:)       :: ct      !! Tabulated function T coordinates
172      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:,:) :: cv      !! Tabulated function values
173      REAL(kind=wp), INTENT(out)                    :: res     !! Interpolated value
174      PROCEDURE(locate)                             :: locator !! Locator function
175      LOGICAL :: ret                                           !! .true. on success, .false. otherwise
176      REAL(kind=wp), DIMENSION(16,5) :: g4d
177      INTEGER                        :: ix0,iy0,iz0,it0
178      INTEGER                        :: i,a,b,c,d
179      ret = .false.
180      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
181      iy0 = locator(y,cy) ; IF (iy0 == 0) RETURN
182      iz0 = locator(z,cz) ; IF (iz0 == 0) RETURN
183      it0 = locator(t,ct) ; IF (it0 == 0) RETURN
184      DO i=1,16
185        a=ix0+MOD((i-1),2)   ; g4d(i,1) = cx(a)
186        b=iy0+MOD((i-1)/2,2) ; g4d(i,2) = cy(b)
187        c=iz0+MOD((i-1)/4,2) ; g4d(i,3) = cz(c)
188        d=it0+MOD((i-1)/8,2) ; g4d(i,4) = ct(d)
189        g4d(i,5) = cv(a,b,c,d)
190      ENDDO
191      res = lintc_((/x,y,z,t/),g4d)
192      ret = .true.
193    END FUNCTION l4d_gen_sc
194 
195    FUNCTION l5d_gen_sc(x,y,z,t,w,cx,cy,cz,ct,cw,cv,locator,res) RESULT(ret)
196      !! Wrapper interface for 5D linear interpolation (scalar)
197      !!
198      !! @warning
199      !! On error, __res__ output value is undefined.
200      REAL(kind=wp), INTENT(in)                       :: x       !! X coordinate of the point to interpolate
201      REAL(kind=wp), INTENT(in)                       :: y       !! Y coordinate of the point to interpolate
202      REAL(kind=wp), INTENT(in)                       :: z       !! Z coordinate of the point to interpolate
203      REAL(kind=wp), INTENT(in)                       :: t       !! T coordinate of the point to interpolate
204      REAL(kind=wp), INTENT(in)                       :: w       !! W coordinate of the point to interpolate
205      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: cx      !! Tabulated function X coordinates
206      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: cy      !! Tabulated function Y coordinates
207      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: cz      !! Tabulated function Z coordinates
208      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: ct      !! Tabulated function T coordinates
209      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: cw      !! Tabulated function W coordinates
210      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:,:,:) :: cv      !! Tabulated function values
211      REAL(kind=wp), INTENT(out)                      :: res     !! Interpolated value
212      PROCEDURE(locate)                               :: locator !! Locator function
213      LOGICAL :: ret                                             !! .true. on success, .false. otherwise
214      REAL(kind=wp), DIMENSION(32,6) :: g5d
215      INTEGER                        :: ix0,iy0,iz0,it0,iw0
216      INTEGER                        :: i,a,b,c,d,e
217      ret = .false.
218      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
219      iy0 = locator(y,cy) ; IF (iy0 == 0) RETURN
220      iz0 = locator(z,cz) ; IF (iz0 == 0) RETURN
221      it0 = locator(t,ct) ; IF (it0 == 0) RETURN
222      iw0 = locator(w,cw) ; IF (iw0 == 0) RETURN
223      DO i=1,32
224        a=ix0+MOD((i-1),2)    ; g5d(i,1) = cx(a)
225        b=iy0+MOD((i-1)/2,2)  ; g5d(i,2) = cy(b)
226        c=iz0+MOD((i-1)/4,2)  ; g5d(i,3) = cz(c)
227        d=it0+MOD((i-1)/8,2)  ; g5d(i,4) = ct(d)
228        e=iw0+MOD((i-1)/16,2) ; g5d(i,5) = cw(e)
229        g5d(i,6) = cv(a,b,c,d,e)
230      ENDDO
231      res = lintc_((/x,y,z,t,w/),g5d)
232      ret = .true.
233    END FUNCTION l5d_gen_sc
234 
235    ! HARD-CODED versions
236    ! -------------------
237 
238    FUNCTION hdcdl1d_gen_sc(x,cx,cv,locator,res) RESULT(ret)
239      !! Hard-coded 1D linear interpolation (scalar)
240      !!
241      !! @warning
242      !! On error, __res__ output value is undefined.
243      REAL(kind=wp), INTENT(in)               :: x       !! X coordinate of the point to interpolate
244      REAL(kind=wp), INTENT(in), DIMENSION(:) :: cx      !! Tabulated function X coordinates
245      REAL(kind=wp), INTENT(in), DIMENSION(:) :: cv      !! Tabulated function values
246      REAL(kind=wp), INTENT(out)              :: res     !! Interpolated value
247      PROCEDURE(locate)                       :: locator !! Locator function
248      LOGICAL :: ret                                     !! .true. on success, .false. otherwise
249      REAL(kind=wp) :: xd
250      INTEGER       :: ix0,ix1
251      ret = .false.
252      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
253      ix1 = ix0+1
254      xd = (x-cx(ix0))/(cx(ix1)-cx(ix0))
255      res = cv(ix0)*(1d0-xd)+cv(ix1)*xd
256      ret = .true.
257    END FUNCTION hdcdl1d_gen_sc
258 
259    FUNCTION hdcdl2d_gen_sc(x,y,cx,cy,cv,locator,res) RESULT(ret)
260      !! Hard-coded 2D linear interpolation (scalar)
261      !!
262      !! @warning
263      !! On error, __res__ output value is undefined.
264      REAL(kind=wp), INTENT(in)                 :: x       !! X coordinate of the point to interpolate
265      REAL(kind=wp), INTENT(in)                 :: y       !! Y coordinate of the point to interpolate
266      REAL(kind=wp), INTENT(in), DIMENSION(:)   :: cx      !! Tabulated function X coordinates
267      REAL(kind=wp), INTENT(in), DIMENSION(:)   :: cy      !! Tabulated function Y coordinates
268      REAL(kind=wp), INTENT(in), DIMENSION(:,:) :: cv      !! Tabulated function values
269      REAL(kind=wp), INTENT(out)                :: res     !! Interpolated value
270      PROCEDURE(locate)                         :: locator !! Locator function
271      LOGICAL :: ret                                       !! .true. on success, .false. otherwise
272      REAL(kind=wp) :: xd,yd
273      REAL(kind=wp) :: f0,f1
274      INTEGER       :: ix0,iy0,ix1,iy1
275      ret = .false.
276      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
277      iy0 = locator(y,cy) ; IF (iy0 == 0) RETURN
278      ix1 = ix0 + 1 ; iy1 = iy0 + 1
279      xd  = (x-cx(ix0))/(cx(ix1)-cx(ix0))
280      yd  = (y-cy(iy0))/(cy(iy1)-cy(iy0))
281      f0  = cv(ix0,iy0)*(1d0-xd)+cv(ix1,iy0)*xd
282      f1  = cv(ix0,iy1)*(1d0-xd)+cv(ix1,iy1)*xd
283      res = f0*(1d0-yd)+f1*yd
284      ret = .true.
285    END FUNCTION hdcdl2d_gen_sc
286 
287    FUNCTION hdcdl3d_gen_sc(x,y,z,cx,cy,cz,cv,locator,res) RESULT(ret)
288      !! Hard-coded 3D linear interpolation (scalar)
289      !!
290      !! @warning
291      !! On error, __res__ output value is undefined.
292      REAL(kind=wp), INTENT(in)                   :: x       !! X coordinate of the point to interpolate
293      REAL(kind=wp), INTENT(in)                   :: y       !! Y coordinate of the point to interpolate
294      REAL(kind=wp), INTENT(in)                   :: z       !! Z coordinate of the point to interpolate
295      REAL(kind=wp), INTENT(in), DIMENSION(:)     :: cx      !! Tabulated function X coordinates
296      REAL(kind=wp), INTENT(in), DIMENSION(:)     :: cy      !! Tabulated function Y coordinates
297      REAL(kind=wp), INTENT(in), DIMENSION(:)     :: cz      !! Tabulated function Z coordinates
298      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:) :: cv      !! Tabulated function values
299      REAL(kind=wp), INTENT(out)                  :: res     !! Interpolated value
300      PROCEDURE(locate)                           :: locator !! Locator function
301      LOGICAL :: ret                                         !! .true. on success, .false. otherwise
302      REAL(kind=wp) :: xd,yd,zd
303      REAL(kind=wp) :: f00,f10,f01,f11,f0,f1
304      INTEGER       :: ix0,iy0,iz0,ix1,iy1,iz1
305      ret = .false.
306      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
307      iy0 = locator(y,cy) ; IF (iy0 == 0) RETURN
308      iz0 = locator(z,cz) ; IF (iz0 == 0) RETURN
309      ix1=ix0+1 ; iy1=iy0+1 ; iz1=iz0+1
310      xd = (x-cx(ix0))/(cx(ix1)-cx(ix0))
311      yd = (y-cy(iy0))/(cy(iy1)-cy(iy0))
312      zd = (z-cz(iz0))/(cz(iz1)-cz(iz0))
313 
314      f00 = cv(ix0,iy0,iz0)*(1d0-xd)+cv(ix1,iy0,iz0)*xd
315      f10 = cv(ix0,iy1,iz0)*(1d0-xd)+cv(ix1,iy1,iz0)*xd
316      f01 = cv(ix0,iy0,iz1)*(1d0-xd)+cv(ix1,iy0,iz1)*xd
317      f11 = cv(ix0,iy1,iz1)*(1d0-xd)+cv(ix1,iy1,iz1)*xd
318 
319      f0 = f00 *(1d0-yd)+f10*yd
320      f1 = f00 *(1d0-yd)+f10*yd
321 
322      res = f0*(1d0-zd)+f1*zd
323      ret = .true.
324    END FUNCTION hdcdl3d_gen_sc
325 
326    FUNCTION hdcdl4d_gen_sc(x,y,z,t,cx,cy,cz,ct,cv,locator,res) RESULT(ret)
327      !! Hard-coded 4D linear interpolation (scalar)
328      !!
329      !! @warning
330      !! On error, __res__ output value is undefined.
331      REAL(kind=wp), INTENT(in)                     :: x       !! X coordinate of the point to interpolate
332      REAL(kind=wp), INTENT(in)                     :: y       !! Y coordinate of the point to interpolate
333      REAL(kind=wp), INTENT(in)                     :: z       !! Z coordinate of the point to interpolate
334      REAL(kind=wp), INTENT(in)                     :: t       !! T coordinate of the point to interpolate
335      REAL(kind=wp), INTENT(in), DIMENSION(:)       :: cx      !! Tabulated function X coordinates
336      REAL(kind=wp), INTENT(in), DIMENSION(:)       :: cy      !! Tabulated function Y coordinates
337      REAL(kind=wp), INTENT(in), DIMENSION(:)       :: cz      !! Tabulated function Z coordinates
338      REAL(kind=wp), INTENT(in), DIMENSION(:)       :: ct      !! Tabulated function T coordinates
339      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:,:) :: cv      !! Tabulated function values
340      REAL(kind=wp), INTENT(out)                    :: res     !! Interpolated value
341      PROCEDURE(locate)                             :: locator !! Locator function
342      LOGICAL :: ret                                           !! .true. on success, .false. otherwise
343      REAL(kind=wp) :: xd,yd,zd,td
344      REAL(kind=wp) :: f000,f100,f010,f110,f001,f101,f011,f111, &
345                       f00,f10,f01,f11,f0,f1
346      INTEGER       :: ix0,iy0,iz0,it0,ix1,iy1,iz1,it1
347      ret = .false.
348      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
349      iy0 = locator(y,cy) ; IF (iy0 == 0) RETURN
350      iz0 = locator(z,cz) ; IF (iz0 == 0) RETURN
351      it0 = locator(t,ct) ; IF (it0 == 0) RETURN
352     
353      ix1=ix0+1 ; iy1=iy0+1 ; iz1=iz0+1 ; it1=it0+1
354      xd = (x-cx(ix0))/(cx(ix1)-cx(ix0))
355      yd = (y-cy(iy0))/(cy(iy1)-cy(iy0))
356      zd = (z-cz(iz0))/(cz(iz1)-cz(iz0))
357      td = (t-ct(it0))/(ct(it1)-ct(it0))
358 
359      f000 = cv(ix0,iy0,iz0,it0)*(1d0-xd)+cv(ix1,iy0,iz0,it0)*xd
360      f100 = cv(ix0,iy1,iz0,it0)*(1d0-xd)+cv(ix1,iy1,iz0,it0)*xd
361      f010 = cv(ix0,iy0,iz1,it0)*(1d0-xd)+cv(ix1,iy0,iz1,it0)*xd
362      f110 = cv(ix0,iy1,iz1,it0)*(1d0-xd)+cv(ix1,iy1,iz1,it0)*xd
363      f001 = cv(ix0,iy0,iz0,it1)*(1d0-xd)+cv(ix1,iy0,iz0,it1)*xd
364      f101 = cv(ix0,iy1,iz0,it1)*(1d0-xd)+cv(ix1,iy1,iz0,it1)*xd
365      f011 = cv(ix0,iy0,iz1,it1)*(1d0-xd)+cv(ix1,iy0,iz1,it1)*xd
366      f111 = cv(ix0,iy1,iz1,it1)*(1d0-xd)+cv(ix1,iy1,iz1,it1)*xd
367 
368      f00 = f000*(1d0-yd)+f100*yd
369      f10 = f010*(1d0-yd)+f110*yd
370      f01 = f001*(1d0-yd)+f101*yd
371      f11 = f011*(1d0-yd)+f111*yd
372 
373      f0 = f00 *(1d0-zd)+f10*zd
374      f1 = f01 *(1d0-zd)+f11*zd
375 
376      res = f0*(1d0-td)+f1*td
377      ret = .true.
378    END FUNCTION hdcdl4d_gen_sc
379 
380    FUNCTION hdcdl5d_gen_sc(x,y,z,t,w,cx,cy,cz,ct,cw,cv,locator,res) RESULT(ret)
381      !! Hard-coded 5D linear interpolation (scalar)
382      !!
383      !! @warning
384      !! On error, __res__ output value is undefined.
385      REAL(kind=wp), INTENT(in)                       :: x       !! X coordinate of the point to interpolate
386      REAL(kind=wp), INTENT(in)                       :: y       !! Y coordinate of the point to interpolate
387      REAL(kind=wp), INTENT(in)                       :: z       !! Z coordinate of the point to interpolate
388      REAL(kind=wp), INTENT(in)                       :: t       !! T coordinate of the point to interpolate
389      REAL(kind=wp), INTENT(in)                       :: w       !! W coordinate of the point to interpolate
390      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: cx      !! Tabulated function X coordinates
391      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: cy      !! Tabulated function Y coordinates
392      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: cz      !! Tabulated function Z coordinates
393      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: ct      !! Tabulated function T coordinates
394      REAL(kind=wp), INTENT(in), DIMENSION(:)         :: cw      !! Tabulated function W coordinates
395      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:,:,:) :: cv      !! Tabulated function values
396      REAL(kind=wp), INTENT(out)                      :: res     !! Interpolated value
397      PROCEDURE(locate)                               :: locator !! Locator function
398      LOGICAL :: ret                                             !! .true. on success, .false. otherwise
399      REAL(kind=wp) :: xd,yd,zd,td,wd
400      REAL(kind=wp) :: f0000,f1000,f0100,f1100,f0010,f1010,f0110,f1110, &
401                       f0001,f1001,f0101,f1101,f0011,f1011,f0111,f1111, &
402                       f000,f100,f010,f110,f001,f101,f011,f111,         &
403                       f00,f10,f01,f11,f0,f1
404      INTEGER       :: ix0,iy0,iz0,it0,iw0,ix1,iy1,iz1,it1,iw1
405      ret = .false.
406      ix0 = locator(x,cx) ; IF (ix0 == 0) RETURN
407      iy0 = locator(y,cy) ; IF (iy0 == 0) RETURN
408      iz0 = locator(z,cz) ; IF (iz0 == 0) RETURN
409      it0 = locator(t,ct) ; IF (it0 == 0) RETURN
410      iw0 = locator(w,cw) ; IF (iw0 == 0) RETURN
411     
412      ix1=ix0+1 ; iy1=iy0+1 ; iz1=iz0+1 ; it1=it0+1 ; iw1=iw0+1
413      xd = (x-cx(ix0))/(cx(ix1)-cx(ix0))
414      yd = (y-cy(iy0))/(cy(iy1)-cy(iy0))
415      zd = (z-cz(iz0))/(cz(iz1)-cz(iz0))
416      td = (t-ct(it0))/(ct(it1)-ct(it0))
417      wd = (w-cw(iw0))/(cw(iw1)-cw(iw0))
418 
419      f0000 = cv(ix0,iy0,iz0,it0,iw0)*(1d0-xd)+cv(ix1,iy0,iz0,it0,iw0)*xd
420      f1000 = cv(ix0,iy1,iz0,it0,iw0)*(1d0-xd)+cv(ix0,iy1,iz0,it0,iw0)*xd
421      f0100 = cv(ix0,iy0,iz1,it0,iw0)*(1d0-xd)+cv(ix1,iy0,iz1,it0,iw0)*xd
422      f1100 = cv(ix0,iy1,iz1,it0,iw0)*(1d0-xd)+cv(ix1,iy1,iz1,it0,iw0)*xd
423      f0010 = cv(ix0,iy0,iz0,it1,iw0)*(1d0-xd)+cv(ix1,iy0,iz0,it1,iw0)*xd
424      f1010 = cv(ix0,iy1,iz0,it1,iw0)*(1d0-xd)+cv(ix1,iy1,iz0,it1,iw0)*xd
425      f0110 = cv(ix0,iy0,iz1,it1,iw0)*(1d0-xd)+cv(ix1,iy0,iz1,it1,iw0)*xd
426      f1110 = cv(ix0,iy1,iz1,it1,iw0)*(1d0-xd)+cv(ix1,iy1,iz1,it1,iw0)*xd
427      f0001 = cv(ix0,iy0,iz0,it0,iw1)*(1d0-xd)+cv(ix1,iy0,iz0,it0,iw1)*xd
428      f1001 = cv(ix0,iy1,iz0,it0,iw1)*(1d0-xd)+cv(ix0,iy1,iz0,it0,iw1)*xd
429      f0101 = cv(ix0,iy0,iz1,it0,iw1)*(1d0-xd)+cv(ix1,iy0,iz1,it0,iw1)*xd
430      f1101 = cv(ix0,iy1,iz1,it0,iw1)*(1d0-xd)+cv(ix1,iy1,iz1,it0,iw1)*xd
431      f0011 = cv(ix0,iy0,iz0,it1,iw1)*(1d0-xd)+cv(ix1,iy0,iz0,it1,iw1)*xd
432      f1011 = cv(ix0,iy1,iz0,it1,iw1)*(1d0-xd)+cv(ix1,iy1,iz0,it1,iw1)*xd
433      f0111 = cv(ix0,iy0,iz1,it1,iw1)*(1d0-xd)+cv(ix1,iy0,iz1,it1,iw1)*xd
434      f1111 = cv(ix0,iy1,iz1,it1,iw1)*(1d0-xd)+cv(ix1,iy1,iz1,it1,iw1)*xd
435 
436      f000 = f0000*(1d0-yd) + f1000*yd
437      f100 = f0100*(1d0-yd) + f1100*yd
438      f010 = f0010*(1d0-yd) + f1010*yd
439      f110 = f0110*(1d0-yd) + f1110*yd
440      f101 = f0101*(1d0-yd) + f1101*yd
441      f011 = f0011*(1d0-yd) + f1011*yd
442      f111 = f0111*(1d0-yd) + f1111*yd
443 
444      f00 = f000*(1d0-zd)+f100*zd
445      f10 = f010*(1d0-zd)+f110*zd
446      f01 = f001*(1d0-zd)+f101*zd
447      f11 = f011*(1d0-zd)+f111*zd
448 
449      f0 = f00 *(1d0-td)+f10*td
450      f1 = f01 *(1d0-td)+f11*td
451 
452      res = f0*(1d0-wd)+f1*wd
453      ret = .true.
454    END FUNCTION hdcdl5d_gen_sc
455 
456    !--------------------
457    ! VECTORIZED VERSIONS
458    !--------------------
459 
460    ! GENERIC versions
461    ! ----------------
462 
463    FUNCTION l1d_gen_ve(x,cx,cv,locator,res) RESULT(ret)
464      !! Wrapper interface for 1D linear interpolation (vector)
465      !!
466      !! @warning
467      !! On error, __res__ output vector is undefined (i.e. not allocated).
468      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
469      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
470      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cv      !! Tabulated function values
471      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
472      PROCEDURE(locate)                                     :: locator !! Locator function
473      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
474      REAL(kind=wp), DIMENSION(2,2) :: g1d
475      INTEGER                       :: n,j,i,ix
476      ret = .false.
477      n = SIZE(x) ; ALLOCATE(res(n))
478      DO j=1,n
479        ix = locator(x(j),cx)
480        IF (ix == 0) THEN
481          DEALLOCATE(res) ; RETURN
482        ENDIF
483        DO i=0,1
484          g1d(i+1,1) = cx(ix+i)
485          g1d(i+1,2) = cv(ix+i)
486        ENDDO
487        res(j) = lintc_((/x(j)/),g1d)
488      ENDDO
489      ret = .true.
490    END FUNCTION l1d_gen_ve
491 
492    FUNCTION l2d_gen_ve(x,y,cx,cy,cv,locator,res) RESULT(ret)
493      !! Wrapper interface for 2D linear interpolation (vector)
494      !!
495      !! @warning
496      !! On error, __res__ output vector is undefined (i.e. not allocated).
497      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
498      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: y       !! Y coordinate of the points to interpolate
499      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
500      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cy      !! Tabulated function Y coordinates
501      REAL(kind=wp), INTENT(in), DIMENSION(:,:)             :: cv      !! Tabulated function values
502      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
503      PROCEDURE(locate)                                     :: locator !! Locator function
504      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
505      REAL(kind=wp), DIMENSION(4,3) :: g2d
506      INTEGER                       :: n,j,ix0,iy0,i,a,b
507      ret = .false.
508      n = SIZE(x) ; ALLOCATE(res(n))
509      DO j=1,n
510        ix0 = locator(x(j),cx)
511        iy0 = locator(y(j),cy)
512        IF (ix0 == 0 .OR. iy0 == 0) THEN
513          DEALLOCATE(res) ; RETURN
514        ENDIF
515        DO i=1,4
516          a=ix0+MOD((i-1),2)   ; g2d(i,1) = cx(a)
517          b=iy0+MOD((i-1)/2,2) ; g2d(i,2) = cy(b)
518          g2d(i,3) = cv(a,b)
519        ENDDO
520        res(j) = lintc_((/x(j),y(j)/),g2d)
521     ENDDO
522      ret = .true.
523    END FUNCTION l2d_gen_ve
524 
525    FUNCTION l3d_gen_ve(x,y,z,cx,cy,cz,cv,locator,res) RESULT(ret)
526      !! Wrapper interface for 3D linear interpolation (vector)
527      !!
528      !! @warning
529      !! On error, __res__ output vector is undefined (i.e. not allocated).
530      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
531      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: y       !! Y coordinate of the points to interpolate
532      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: z       !! Z coordinate of the points to interpolate
533      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
534      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cy      !! Tabulated function Y coordinates
535      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cz      !! Tabulated function Z coordinates
536      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:)           :: cv      !! Tabulated function values
537      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
538      PROCEDURE(locate)                                     :: locator !! Locator function
539      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
540      REAL(kind=wp), DIMENSION(8,4) :: g3d
541      INTEGER                       :: ix0,iy0,iz0
542      INTEGER                       :: n,j,i,a,b,c
543      ret = .false.
544      n = SIZE(x) ; ALLOCATE(res(n))
545      DO j=1,n
546        ix0 = locator(x(j),cx)
547        iy0 = locator(y(j),cy)
548        iz0 = locator(z(j),cz)
549        IF (ix0 == 0 .OR. iy0 == 0 .OR. iz0 == 0) THEN
550          DEALLOCATE(res) ; RETURN
551        ENDIF
552        DO i=1,8
553          a=ix0+MOD((i-1),2)   ; g3d(i,1) = cx(a)
554          b=iy0+MOD((i-1)/2,2) ; g3d(i,2) = cy(b)
555          c=iz0+MOD((i-1)/4,2) ; g3d(i,3) = cz(c)
556          g3d(i,4) = cv(a,b,c)
557        ENDDO
558        res(j) = lintc_((/x(j),y(j),z(j)/),g3d)
559      ENDDO
560      ret = .true.
561    END FUNCTION l3d_gen_ve
562 
563    FUNCTION l4d_gen_ve(x,y,z,t,cx,cy,cz,ct,cv,locator,res) RESULT(ret)
564      !! Wrapper interface for 4D linear interpolation (vector)
565      !!
566      !! @warning
567      !! On error, __res__ output vector is undefined (i.e. not allocated).
568      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
569      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: y       !! Y coordinate of the points to interpolate
570      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: z       !! Z coordinate of the points to interpolate
571      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: t       !! T coordinate of the points to interpolate
572      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
573      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cy      !! Tabulated function Y coordinates
574      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cz      !! Tabulated function Z coordinates
575      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: ct      !! Tabulated function T coordinates
576      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:,:)         :: cv      !! Tabulated function values
577      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
578      PROCEDURE(locate)                                     :: locator !! Locator function
579      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
580      REAL(kind=wp), DIMENSION(16,5) :: g4d
581      INTEGER                        :: ix0,iy0,iz0,it0
582      INTEGER                        :: n,j,i,a,b,c,d
583      ret = .false.
584      n = SIZE(x) ; ALLOCATE(res(n))
585      DO j=1,n
586        ix0 = locator(x(j),cx)
587        iy0 = locator(y(j),cy)
588        iz0 = locator(z(j),cz)
589        it0 = locator(t(j),ct)
590        IF (ix0 == 0 .OR. iy0 == 0 .OR. iz0 == 0 .OR. it0 == 0) THEN
591          DEALLOCATE(res) ; RETURN
592        ENDIF
593        DO i=1,16
594          a=ix0+MOD((i-1),2)   ; g4d(i,1) = cx(a)
595          b=iy0+MOD((i-1)/2,2) ; g4d(i,2) = cy(b)
596          c=iz0+MOD((i-1)/4,2) ; g4d(i,3) = cz(c)
597          d=it0+MOD((i-1)/8,2) ; g4d(i,4) = ct(d)
598          g4d(i,5) = cv(a,b,c,d)
599        ENDDO
600        res(j) = lintc_((/x(j),y(j),z(j),t(j)/),g4d)
601      ENDDO
602      ret = .true.
603    END FUNCTION l4d_gen_ve
604 
605    FUNCTION l5d_gen_ve(x,y,z,t,w,cx,cy,cz,ct,cw,cv,locator,res) RESULT(ret)
606      !! Wrapper interface for 5D linear interpolation (vector)
607      !!
608      !! @warning
609      !! On error, __res__ output vector is undefined (i.e. not allocated).
610      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
611      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: y       !! Y coordinate of the points to interpolate
612      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: z       !! Z coordinate of the points to interpolate
613      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: t       !! T coordinate of the points to interpolate
614      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: w       !! W coordinate of the points to interpolate
615      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
616      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cy      !! Tabulated function Y coordinates
617      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cz      !! Tabulated function Z coordinates
618      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: ct      !! Tabulated function T coordinates
619      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cw      !! Tabulated function W coordinates
620      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:,:,:)       :: cv      !! Tabulated function values
621      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
622      PROCEDURE(locate)                                     :: locator !! Locator function
623      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
624      REAL(kind=wp), DIMENSION(32,6) :: g5d
625      INTEGER                        :: ix0,iy0,iz0,it0,iw0
626      INTEGER                        :: n,j,i,a,b,c,d,e
627      ret = .false.
628      n = SIZE(x) ; ALLOCATE(res(n))
629      DO j=1,n
630        ix0 = locator(x(j),cx)
631        iy0 = locator(y(j),cy)
632        iz0 = locator(z(j),cz)
633        it0 = locator(t(j),ct)
634        iw0 = locator(w(j),cw)
635        IF (ix0 == 0 .OR. iy0 == 0 .OR. iz0 == 0 .OR. it0 == 0 .OR. iw0 == 0) THEN
636          DEALLOCATE(res) ; RETURN
637        ENDIF
638        DO i=1,32
639          a=ix0+MOD((i-1),2)    ; g5d(i,1) = cx(a)
640          b=iy0+MOD((i-1)/2,2)  ; g5d(i,2) = cy(b)
641          c=iz0+MOD((i-1)/4,2)  ; g5d(i,3) = cz(c)
642          d=it0+MOD((i-1)/8,2)  ; g5d(i,4) = ct(d)
643          e=iw0+MOD((i-1)/16,2) ; g5d(i,5) = cw(e)
644          g5d(i,6) = cv(a,b,c,d,e)
645        ENDDO
646        res(j) = lintc_((/x,y,z,t,w/),g5d)
647      ENDDO
648      ret = .true.
649    END FUNCTION l5d_gen_ve
650 
651    ! HARD-CODED versions
652    ! -------------------
653 
654    FUNCTION hdcdl1d_gen_ve(x,cx,cv,locator,res) RESULT(ret)
655      !! Hard-coded 1D linear interpolation (vector)
656      !!
657      !! @warning
658      !! On error, __res__ output vector is undefined (i.e. not allocated).
659      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
660      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
661      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cv      !! Tabulated function values
662      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
663      PROCEDURE(locate)                                     :: locator !! Locator function
664      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
665      REAL(kind=wp) :: xd
666      INTEGER       :: ix0,ix1
667      INTEGER       :: n,j
668      ret = .false.
669      n = SIZE(x) ; ALLOCATE(res(n))
670      DO j=1,n
671        ix0 = locator(x(j),cx)
672        IF (ix0 == 0) THEN
673          DEALLOCATE(res) ; RETURN
674        ENDIF
675        ix1 = ix0+1
676        xd = (x(j)-cx(ix0))/(cx(ix1)-cx(ix0))
677        res(j) = cv(ix0)*(1d0-xd)+cv(ix1)*xd
678      ENDDO
679      ret = .true.
680    END FUNCTION hdcdl1d_gen_ve
681 
682    FUNCTION hdcdl2d_gen_ve(x,y,cx,cy,cv,locator,res) RESULT(ret)
683      !! Hard-coded 2D linear interpolation (vector)
684      !!
685      !! @warning
686      !! On error, __res__ output vector is undefined (i.e. not allocated).
687      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
688      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: y       !! Y coordinate of the points to interpolate
689      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
690      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cy      !! Tabulated function Y coordinates
691      REAL(kind=wp), INTENT(in), DIMENSION(:,:)             :: cv      !! Tabulated function values
692      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
693      PROCEDURE(locate)                                     :: locator !! Locator function
694      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
695      REAL(kind=wp) :: xd,yd
696      REAL(kind=wp) :: f0,f1
697      INTEGER       :: ix0,iy0,ix1,iy1
698      INTEGER       :: n,j
699      ret = .false.
700      n = SIZE(x) ; ALLOCATE(res(n))
701      DO j=1,n
702        ix0 = locator(x(j),cx)
703        iy0 = locator(y(j),cy)
704        IF (ix0 == 0 .OR. iy0 == 0) THEN
705          DEALLOCATE(res) ; RETURN
706        ENDIF
707        ix1 = ix0 + 1 ; iy1 = iy0 + 1
708        xd  = (x(j)-cx(ix0))/(cx(ix1)-cx(ix0))
709        yd  = (y(j)-cy(iy0))/(cy(iy1)-cy(iy0))
710        f0  = cv(ix0,iy0)*(1d0-xd)+cv(ix1,iy0)*xd
711        f1  = cv(ix0,iy1)*(1d0-xd)+cv(ix1,iy1)*xd
712        res(j) = f0*(1d0-yd)+f1*yd
713      ENDDO
714      ret = .true.
715    END FUNCTION hdcdl2d_gen_ve
716 
717    FUNCTION hdcdl3d_gen_ve(x,y,z,cx,cy,cz,cv,locator,res) RESULT(ret)
718      !! Hard-coded 3D linear interpolation (vector)
719      !!
720      !! @warning
721      !! On error, __res__ output vector is undefined (i.e. not allocated).
722      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
723      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: y       !! Y coordinate of the points to interpolate
724      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: z       !! Z coordinate of the points to interpolate
725      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
726      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cy      !! Tabulated function Y coordinates
727      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cz      !! Tabulated function Z coordinates
728      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:)           :: cv      !! Tabulated function values
729      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
730      PROCEDURE(locate)                                     :: locator !! Locator function
731      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
732      REAL(kind=wp) :: xd,yd,zd
733      REAL(kind=wp) :: f00,f10,f01,f11,f0,f1
734      INTEGER       :: ix0,iy0,iz0,ix1,iy1,iz1
735      INTEGER       :: n,j
736      ret = .false.
737      n = SIZE(x) ; ALLOCATE(res(n))
738      DO j=1,n
739        ix0 = locator(x(j),cx)
740        iy0 = locator(y(j),cy)
741        iz0 = locator(z(j),cz)
742        IF (ix0 == 0 .OR. iy0 == 0 .OR. iz0 == 0) THEN
743          DEALLOCATE(res) ; RETURN
744        ENDIF
745        ix1=ix0+1 ; iy1=iy0+1 ; iz1=iz0+1
746        xd = (x(j)-cx(ix0))/(cx(ix1)-cx(ix0))
747        yd = (y(j)-cy(iy0))/(cy(iy1)-cy(iy0))
748        zd = (z(j)-cz(iz0))/(cz(iz1)-cz(iz0))
749 
750        f00 = cv(ix0,iy0,iz0)*(1d0-xd)+cv(ix1,iy0,iz0)*xd
751        f10 = cv(ix0,iy1,iz0)*(1d0-xd)+cv(ix1,iy1,iz0)*xd
752        f01 = cv(ix0,iy0,iz1)*(1d0-xd)+cv(ix1,iy0,iz1)*xd
753        f11 = cv(ix0,iy1,iz1)*(1d0-xd)+cv(ix1,iy1,iz1)*xd
754 
755        f0 = f00 *(1d0-yd)+f10*yd
756        f1 = f00 *(1d0-yd)+f10*yd
757 
758        res(j) = f0*(1d0-zd)+f1*zd
759      ENDDO
760      ret = .true.
761    END FUNCTION hdcdl3d_gen_ve
762 
763    FUNCTION hdcdl4d_gen_ve(x,y,z,t,cx,cy,cz,ct,cv,locator,res) RESULT(ret)
764      !! Hard-coded 4D linear interpolation (vector)
765      !!
766      !! @warning
767      !! On error, __res__ output vector is undefined (i.e. not allocated).
768      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
769      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: y       !! Y coordinate of the points to interpolate
770      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: z       !! Z coordinate of the points to interpolate
771      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: t       !! T coordinate of the points to interpolate
772      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
773      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cy      !! Tabulated function Y coordinates
774      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cz      !! Tabulated function Z coordinates
775      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: ct      !! Tabulated function T coordinates
776      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:,:)         :: cv      !! Tabulated function values
777      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
778      PROCEDURE(locate)                                     :: locator !! Locator function
779      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
780      REAL(kind=wp) :: xd,yd,zd,td
781      REAL(kind=wp) :: f000,f100,f010,f110,f001,f101,f011,f111, &
782                       f00,f10,f01,f11,f0,f1
783      INTEGER       :: ix0,iy0,iz0,it0,ix1,iy1,iz1,it1
784      INTEGER       :: n,j
785      ret = .false.
786      n = SIZE(x) ; ALLOCATE(res(n))
787      DO j=1,n
788        ix0 = locator(x(j),cx)
789        iy0 = locator(y(j),cy)
790        iz0 = locator(z(j),cz)
791        it0 = locator(t(j),ct)
792        IF (ix0 == 0 .OR. iy0 == 0 .OR. iz0 == 0 .OR. it0 == 0) THEN
793          DEALLOCATE(res) ; RETURN
794        ENDIF
795        ix1=ix0+1 ; iy1=iy0+1 ; iz1=iz0+1 ; it1=it0+1
796        xd = (x(j)-cx(ix0))/(cx(ix1)-cx(ix0))
797        yd = (y(j)-cy(iy0))/(cy(iy1)-cy(iy0))
798        zd = (z(j)-cz(iz0))/(cz(iz1)-cz(iz0))
799        td = (t(j)-ct(it0))/(ct(it1)-ct(it0))
800 
801        f000 = cv(ix0,iy0,iz0,it0)*(1d0-xd)+cv(ix1,iy0,iz0,it0)*xd
802        f100 = cv(ix0,iy1,iz0,it0)*(1d0-xd)+cv(ix1,iy1,iz0,it0)*xd
803        f010 = cv(ix0,iy0,iz1,it0)*(1d0-xd)+cv(ix1,iy0,iz1,it0)*xd
804        f110 = cv(ix0,iy1,iz1,it0)*(1d0-xd)+cv(ix1,iy1,iz1,it0)*xd
805        f001 = cv(ix0,iy0,iz0,it1)*(1d0-xd)+cv(ix1,iy0,iz0,it1)*xd
806        f101 = cv(ix0,iy1,iz0,it1)*(1d0-xd)+cv(ix1,iy1,iz0,it1)*xd
807        f011 = cv(ix0,iy0,iz1,it1)*(1d0-xd)+cv(ix1,iy0,iz1,it1)*xd
808        f111 = cv(ix0,iy1,iz1,it1)*(1d0-xd)+cv(ix1,iy1,iz1,it1)*xd
809 
810        f00 = f000*(1d0-yd)+f100*yd
811        f10 = f010*(1d0-yd)+f110*yd
812        f01 = f001*(1d0-yd)+f101*yd
813        f11 = f011*(1d0-yd)+f111*yd
814 
815        f0 = f00 *(1d0-zd)+f10*zd
816        f1 = f01 *(1d0-zd)+f11*zd
817   
818        res(j) = f0*(1d0-td)+f1*td
819      ENDDO
820      ret = .true.
821    END FUNCTION hdcdl4d_gen_ve
822 
823    FUNCTION hdcdl5d_gen_ve(x,y,z,t,w,cx,cy,cz,ct,cw,cv,locator,res) RESULT(ret)
824      !! Hard-coded 5D linear interpolation (vector)
825      !!
826      !! @warning
827      !! On error, __res__ output vector is undefined (i.e. not allocated).
828      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: x       !! X coordinate of the points to interpolate
829      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: y       !! Y coordinate of the points to interpolate
830      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: z       !! Z coordinate of the points to interpolate
831      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: t       !! T coordinate of the points to interpolate
832      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: w       !! W coordinate of the points to interpolate
833      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cx      !! Tabulated function X coordinates
834      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cy      !! Tabulated function Y coordinates
835      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cz      !! Tabulated function Z coordinates
836      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: ct      !! Tabulated function T coordinates
837      REAL(kind=wp), INTENT(in), DIMENSION(:)               :: cw      !! Tabulated function W coordinates
838      REAL(kind=wp), INTENT(in), DIMENSION(:,:,:,:,:)       :: cv      !! Tabulated function values
839      REAL(kind=wp), INTENT(out), DIMENSION(:), ALLOCATABLE :: res     !! Interpolated values
840      PROCEDURE(locate)                                     :: locator !! Locator function
841      LOGICAL :: ret                                                   !! .true. on success, .false. otherwise
842      REAL(kind=wp) :: xd,yd,zd,td,wd
843      REAL(kind=wp) :: f0000,f1000,f0100,f1100,f0010,f1010,f0110,f1110, &
844                       f0001,f1001,f0101,f1101,f0011,f1011,f0111,f1111, &
845                       f000,f100,f010,f110,f001,f101,f011,f111,         &
846                       f00,f10,f01,f11,f0,f1
847      INTEGER       :: ix0,iy0,iz0,it0,iw0,ix1,iy1,iz1,it1,iw1
848      INTEGER       :: n,j
849      ret = .false.
850      n = SIZE(x) ; ALLOCATE(res(n))
851      DO j=1,n
852        ix0 = locator(x(j),cx)
853        iy0 = locator(y(j),cy)
854        iz0 = locator(z(j),cz)
855        it0 = locator(t(j),ct)
856        iw0 = locator(w(j),cw)
857        IF (ix0 == 0 .OR. iy0 == 0 .OR. iz0 == 0 .OR. it0 == 0 .OR. iw0 == 0) THEN
858          DEALLOCATE(res) ; RETURN
859        ENDIF
860        ix1=ix0+1 ; iy1=iy0+1 ; iz1=iz0+1 ;
861        xd = (x(j)-cx(ix0))/(cx(ix1)-cx(ix0))
862        yd = (y(j)-cy(iy0))/(cy(iy1)-cy(iy0))
863        zd = (z(j)-cz(iz0))/(cz(iz1)-cz(iz0))
864        td = (t(j)-ct(it0))/(ct(it1)-ct(it0))
865        wd = (w(j)-cw(it0))/(cw(it1)-cw(it0))
866 
867        f0000 = cv(ix0,iy0,iz0,it0,iw0)*(1d0-xd)+cv(ix1,iy0,iz0,it0,iw0)*xd
868        f1000 = cv(ix0,iy1,iz0,it0,iw0)*(1d0-xd)+cv(ix0,iy1,iz0,it0,iw0)*xd
869        f0100 = cv(ix0,iy0,iz1,it0,iw0)*(1d0-xd)+cv(ix1,iy0,iz1,it0,iw0)*xd
870        f1100 = cv(ix0,iy1,iz1,it0,iw0)*(1d0-xd)+cv(ix1,iy1,iz1,it0,iw0)*xd
871        f0010 = cv(ix0,iy0,iz0,it1,iw0)*(1d0-xd)+cv(ix1,iy0,iz0,it1,iw0)*xd
872        f1010 = cv(ix0,iy1,iz0,it1,iw0)*(1d0-xd)+cv(ix1,iy1,iz0,it1,iw0)*xd
873        f0110 = cv(ix0,iy0,iz1,it1,iw0)*(1d0-xd)+cv(ix1,iy0,iz1,it1,iw0)*xd
874        f1110 = cv(ix0,iy1,iz1,it1,iw0)*(1d0-xd)+cv(ix1,iy1,iz1,it1,iw0)*xd
875        f0001 = cv(ix0,iy0,iz0,it0,iw1)*(1d0-xd)+cv(ix1,iy0,iz0,it0,iw1)*xd
876        f1001 = cv(ix0,iy1,iz0,it0,iw1)*(1d0-xd)+cv(ix0,iy1,iz0,it0,iw1)*xd
877        f0101 = cv(ix0,iy0,iz1,it0,iw1)*(1d0-xd)+cv(ix1,iy0,iz1,it0,iw1)*xd
878        f1101 = cv(ix0,iy1,iz1,it0,iw1)*(1d0-xd)+cv(ix1,iy1,iz1,it0,iw1)*xd
879        f0011 = cv(ix0,iy0,iz0,it1,iw1)*(1d0-xd)+cv(ix1,iy0,iz0,it1,iw1)*xd
880        f1011 = cv(ix0,iy1,iz0,it1,iw1)*(1d0-xd)+cv(ix1,iy1,iz0,it1,iw1)*xd
881        f0111 = cv(ix0,iy0,iz1,it1,iw1)*(1d0-xd)+cv(ix1,iy0,iz1,it1,iw1)*xd
882        f1111 = cv(ix0,iy1,iz1,it1,iw1)*(1d0-xd)+cv(ix1,iy1,iz1,it1,iw1)*xd
883 
884        f000 = f0000*(1d0-yd) + f1000*yd
885        f100 = f0100*(1d0-yd) + f1100*yd
886        f010 = f0010*(1d0-yd) + f1010*yd
887        f110 = f0110*(1d0-yd) + f1110*yd
888        f101 = f0101*(1d0-yd) + f1101*yd
889        f011 = f0011*(1d0-yd) + f1011*yd
890        f111 = f0111*(1d0-yd) + f1111*yd
891 
892        f00 = f000*(1d0-zd)+f100*zd
893        f10 = f010*(1d0-zd)+f110*zd
894        f01 = f001*(1d0-zd)+f101*zd
895        f11 = f011*(1d0-zd)+f111*zd
896 
897        f0 = f00 *(1d0-td)+f10*td
898        f1 = f01 *(1d0-td)+f11*td
899 
900        res(j) = f0*(1d0-wd)+f1*wd
901      ENDDO
902      ret = .true.
903    END FUNCTION hdcdl5d_gen_ve
904 
905  END MODULE LINT_GEN 
Note: See TracBrowser for help on using the repository browser.