SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
interpol_ts_water_mth.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_ts_water_mth (W, &
7  kyear,kmonth,kday,pts)
8 ! #######################################################
9 !
10 !!**** *INTERPOL_TS_WATER_MTH* - Interpolation of monthly TS water
11 !!
12 !! PURPOSE
13 !! -------
14 !!
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !! AUTHOR
30 !! ------
31 !!
32 ! B.Decharme Meteo-France
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 28/01/10
37 !! Modified 07/2015 B. Decharme : new linear interpolation
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
44 !
45 USE modd_watflux_n, ONLY : watflux_t
46 !
47 USE modi_interpol_quadra
48 USE modi_interpol_linear
49 !
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(watflux_t), INTENT(INOUT) :: w
62 !
63 INTEGER, INTENT(IN ) :: kyear ! year of date
64 INTEGER, INTENT(IN ) :: kmonth ! month of date
65 INTEGER, INTENT(IN ) :: kday ! day of date
66 !
67 REAL, DIMENSION(:), INTENT(OUT) :: pts ! Water surface temperature at time t
68 !
69 !* 0.2 Declaration of local variables
70 ! ------------------------------
71 !
72 REAL :: zdat ! current day in the current month
73 REAL :: zndat ! number of days in the current month
74 INTEGER :: imth0 ! previous month
75 INTEGER :: imth1 ! current month
76 INTEGER :: imth2 ! next month
77 INTEGER :: indays ! number of days in KMONTH
78 !
79 INTEGER :: idelta
80 !
81 REAL(KIND=JPRB) :: zhook_handle
82 !-------------------------------------------------------------------------------
83 !
84 !* 1. Number of days in a month
85 ! -------------------------
86 !
87 IF (lhook) CALL dr_hook('INTERPOL_TS_WATER_MTH',0,zhook_handle)
88 SELECT CASE (kmonth)
89  CASE(4,6,9,11)
90  indays=30
91  CASE(1,3,5,7:8,10,12)
92  indays=31
93  CASE(2)
94  IF( ((mod(kyear,4)==0).AND.(mod(kyear,100)/=0)) .OR. (mod(kyear,400)==0))THEN
95  indays=29
96  ELSE
97  indays=28
98  ENDIF
99 END SELECT
100 !
101 !
102 !-------------------------------------------------------------------------------
103 !
104 !* 2. TS water Interpolation using previous, current and next month
105 ! -------------------------------------------------------------
106 !
107 zdat = REAL(kday)
108 zndat= REAL(indays)
109 !
110 ! The current month correspond to the indice 2 (or 3 if next month))
111 !
112 IF (kmonth==w%TZTIME%TDATE%MONTH) THEN
113  idelta=0
114 ELSE
115  idelta=1
116 END IF
117 !
118 imth0=1+idelta
119 imth1=2+idelta
120 imth2=3+idelta
121 !
122 IF(w%CINTERPOL_TS=='QUADRA')THEN
123  CALL interpol_quadra(zdat,zndat,w%XTS_MTH(:,imth0),w%XTS_MTH(:,imth1),w%XTS_MTH(:,imth2),pts)
124 ELSEIF(w%CINTERPOL_TS=='LINEAR')THEN
125  CALL interpol_linear(zdat,zndat,w%XTS_MTH(:,imth0),w%XTS_MTH(:,imth1),w%XTS_MTH(:,imth2),pts)
126 ELSEIF(w%CINTERPOL_TS=='UNIF')THEN
127  pts(:) = w%XTS_MTH(:,imth1)
128 ELSE
129  CALL abor1_sfx('INTERPOL_TS_WATER_MTH: interpolation method not supported')
130 ENDIF
131 !
132 IF (lhook) CALL dr_hook('INTERPOL_TS_WATER_MTH',1,zhook_handle)
133 !
134 !-------------------------------------------------------------------------------
135 !
136 END SUBROUTINE interpol_ts_water_mth
subroutine interpol_quadra(PDAT, PNDAT, PVAL0, PVAL1, PVAL2, POUT)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:6
subroutine interpol_ts_water_mth(W, KYEAR, KMONTH, KDAY, PTS)
subroutine interpol_linear(PDAT, PNDAT, PVAL0, PVAL1, PVAL2, POUT)