source: trunk/LMDZ.TITAN/libf/muphytitan/lintcore.f90 @ 1793

Last change on this file since 1793 was 1793, checked in by jvatant, 7 years ago

Making Titan's hazy again, part I
+ Added the source folder libf/muphytitan which contains

YAMMS ( Titan's microphysical model ) from J. Burgalat

+ Modif. compilation files linked to this change
JVO

File size: 4.5 KB
Line 
1! Copyright Université Reims Champagnne-Ardenne (2010-2015)
2! contributor: Jérémie Burgalat
3!
4! jeremie.burgalat@univ-reims.fr
5!
6! This software is a computer program whose purpose is to compute multi-variate
7! linear interpolation.
8!
9! This software is governed by the CeCILL-B license under French law and
10! abiding by the rules of distribution of free software.  You can  use,
11! modify and/ or redistribute the software under the terms of the CeCILL-B
12! license as circulated by CEA, CNRS and INRIA at the following URL
13! "http://www.cecill.info".
14!
15! As a counterpart to the access to the source code and  rights to copy,
16! modify and redistribute granted by the license, users are provided only
17! with a limited warranty  and the software's author,  the holder of the
18! economic rights,  and the successive licensors  have only  limited
19! liability.
20!
21! In this respect, the user's attention is drawn to the risks associated
22! with loading,  using,  modifying and/or developing or reproducing the
23! software by the user in light of its specific status of free software,
24! that may mean  that it is complicated to manipulate,  and  that  also
25! therefore means  that it is reserved for developers  and  experienced
26! professionals having in-depth computer knowledge. Users are therefore
27! encouraged to load and test the software's suitability as regards their
28! requirements in conditions enabling the security of their systems and/or
29! data to be ensured and,  more generally, to use and operate it in the
30! same conditions as regards security.
31!
32! The fact that you are presently reading this means that you have had
33! knowledge of the CeCILL-B license and that you accept its terms.
34
35!! file: lintcore.f90
36!! summary: linear interpolation core function file
37!! author: burgalat
38!! date: 2010-2014
39
40MODULE LINTCORE
41  !! Core module of the library.
42  !!
43  !! This module contains a single function that performs the linear
44  !! interpolation of a single _N_-D point between \(2^{N}\) adjacents
45  !! points.
46  USE LINT_PREC
47  IMPLICIT NONE
48
49  PRIVATE :: wp ! from LINT_PREC
50
51  INTERFACE
52    FUNCTION locate(value,vector) RESULT(idx)
53      !! Locate the nearest default value in vector
54      !!
55      !! the method should search the subscript of the nearest value by default in
56      !! in the input vector.
57      IMPORT wp
58      REAL(kind=wp), INTENT(in)               :: value   !! value to search
59      REAL(kind=wp), INTENT(in), DIMENSION(:) :: vector  !! Vector to search in
60      INTEGER :: idx                                     !! Subscript of the nearest value in vector
61    END FUNCTION locate
62  END INTERFACE
63
64
65  CONTAINS
66
67  FUNCTION lintc_(point,grid) RESULT(res)
68    !! Multivariate linear interpolation core function
69    !!
70    !! The method computes multivariate linear interpolation at the given __point__ using its
71    !! neighbours given in __grid__.
72    !!
73    !! @warning
74    !! In order to get a correct result, __grid__ must be ordered so first dimensions vary first
75    !! (see [Generic method](page/index.html/#generic-method) section of main documentation).
76    !!
77    !! @warning
78    !! The method in its current version does not check array boundaries. This operation should be
79    !! performed in wrappers of the function !
80    INTEGER, PARAMETER :: np = 2
81    REAL(kind=wp), INTENT(in), DIMENSION(:)   :: point
82      !! Coordinates of the point to compute.
83      !!
84      !! For __N__-D interpolation, ut should be a vector of __N__ points.
85    REAL(kind=wp), INTENT(in), DIMENSION(:,:) :: grid
86      !! Grid of values used for interpolation.
87      !!
88      !! For __N__-D interpolation, it should be a 2D-array of \(2^{N}\) rows and \(N+1\) columns.
89      !! Each row corresponds to a point with N coordinates, the last column is reserved for the
90      !! value of the point.
91    REAL(kind=wp) :: res
92      !! Interpolated value
93    REAL(kind=wp), DIMENSION(:),ALLOCATABLE :: val
94    REAL(kind=wp)                           :: cd
95    INTEGER                                 :: nv,mi,ngp,cp,i,j,k
96    nv = SIZE(point) ; mi = np**nv
97    ALLOCATE(val(2*mi-1))
98    val(1:mi) = grid(:,nv+1) ; val(mi+1:2*mi-1) = 0._wp
99    ! Computes the QnD linear interpolation
100    cp = 0
101    DO i=1,nv
102      cd = (point(i)-grid(1,i))/(grid(mi,i)-grid(1,i))
103      k = 1 ; ngp = np**(nv-i+1) ; cp = cp + ngp
104      DO j=1,ngp,np
105        val(cp+k) = val(j+cp-ngp) * (1._wp - cd) + val(j+cp-ngp+1)*cd
106        k = k + 1
107      ENDDO
108    ENDDO
109    res = val(cp+k-1)
110    DEALLOCATE(val) ! useless normally
111    RETURN
112  END FUNCTION lintc_
113
114END MODULE LINTCORE
Note: See TracBrowser for help on using the repository browser.