SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
interpol_quadra.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_quadra(PDAT,PNDAT,PVAL0,PVAL1,PVAL2,POUT)
7 ! #############################################################
8 !
9 !!**** *INTERPOL_QUADRA* Quadractic interpolation between 3 month, especially
10 !! relevant to conserv the SST (or other) monthly mean value.
11 !!
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !! METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 !! B. Decharme Meteo-France
33 !!
34 !! MODIFICATION
35 !! ------------
36 !!
37 !! Original 08/2009
38 !! 18-11-2010 by F. Chauvin : bugfix for temporal interpolation coeff.
39 !!
40 !----------------------------------------------------------------------------
41 !
42 !* 0. DECLARATION
43 ! -----------
44 !
45 !
46 !
47 USE yomhook ,ONLY : lhook, dr_hook
48 USE parkind1 ,ONLY : jprb
49 !
50 IMPLICIT NONE
51 !
52 !* 0.1 Declaration of arguments
53 ! ------------------------
54 !
55 REAL, INTENT(IN) :: pdat ! Present date in the current month
56 REAL, INTENT(IN) :: pndat ! Number of date in the current month
57 REAL, DIMENSION(:), INTENT(IN) :: pval0 ! Value of the precedent month
58 REAL, DIMENSION(:), INTENT(IN) :: pval1 ! Value of the current month
59 REAL, DIMENSION(:), INTENT(IN) :: pval2 ! Value of the next month
60 REAL, DIMENSION(:), INTENT(OUT) :: pout ! Interpolated value
61 !
62 !
63 !* 0.2 Declaration of other local variables
64 ! ------------------------------------
65 !
66 REAL, DIMENSION(SIZE(PVAL0)) :: zmid1 ! Mid point between t-1 and t
67 REAL, DIMENSION(SIZE(PVAL0)) :: zmid2 ! Mid point between t+1 and t
68 REAL, DIMENSION(SIZE(PVAL0)) :: za ! Interpolation coef
69 REAL, DIMENSION(SIZE(PVAL0)) :: zb ! Interpolation coef
70 REAL, DIMENSION(SIZE(PVAL0)) :: zc ! Interpolation coef
71 !
72 REAL :: zscarre ! Quadratic coef
73 REAL :: zsum ! Quadratic coef
74 !
75 INTEGER :: jdat, indat
76 !
77 REAL(KIND=JPRB) :: zhook_handle
78 !
79 !----------------------------------------------------------------------------
80 !
81 IF (lhook) CALL dr_hook('INTERPOL_QUADRA',0,zhook_handle)
82 !
83 !* 1. Initialization
84 ! --------------
85 !
86 zscarre = 0.0
87 zsum = 0.0
88 !
89 indat = int(pndat)
90 !
91 DO jdat=1,indat
92  zscarre = zscarre + REAL(jdat*jdat)
93  zsum = zsum + REAL(jdat)
94 ENDDO
95 !
96 !* 2. Mid points
97 ! ----------
98 !
99 zmid1(:) = 0.5 * (pval1(:)+pval0(:))
100 zmid2(:) = 0.5 * (pval1(:)+pval2(:))
101 !
102 !
103 !* 3. Coef calculation
104 ! ----------------
105 !
106 za(:) = ((pval1(:)-zmid1(:))*pndat - (zmid2(:)-zmid1(:))*(zsum-pndat)/pndat) &
107  / ((zscarre-pndat)-(zsum-pndat)*(pndat+2.0))
108 !
109 zb(:) = ((zmid2(:)-zmid1(:)) - (pndat*(pndat+2.0) * za(:))) / pndat
110 !
111 zc(:) = zmid1(:) - za(:) - zb(:)
112 !
113 !* 3. Final calculation
114 ! -----------------
115 !
116 pout(:) = za(:) * pdat**2 + zb(:) * pdat + zc(:)
117 !
118 !* 4. End
119 ! ---
120 !
121 IF (lhook) CALL dr_hook('INTERPOL_QUADRA',1,zhook_handle)
122 !
123 !-------------------------------------------------------------------------------
124 !
125 END SUBROUTINE interpol_quadra
subroutine interpol_quadra(PDAT, PNDAT, PVAL0, PVAL1, PVAL2, POUT)