SURFEX v8.1
General documentation of Surfex
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 ! #######################################################
8 !
9 !!**** *INTERPOL_TS_WATER_MTH* - Interpolation of monthly TS water
10 !!
11 !! PURPOSE
12 !! -------
13 !!
14 !!
15 !!** METHOD
16 !! ------
17 !!
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !! IMPLICIT ARGUMENTS
23 !! ------------------
24 !!
25 !! REFERENCE
26 !! ---------
27 !!
28 !! AUTHOR
29 !! ------
30 !!
31 ! B.Decharme Meteo-France
32 !!
33 !! MODIFICATIONS
34 !! -------------
35 !! Original 28/01/10
36 !! Modified 07/2015 B. Decharme : new linear interpolation
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 !
43 !
44 USE modd_watflux_n, ONLY : watflux_t
45 !
46 USE modi_interpol_quadra
47 USE modi_interpol_linear
48 !
49 USE modi_abor1_sfx
50 !
51 USE yomhook ,ONLY : lhook, dr_hook
52 USE parkind1 ,ONLY : jprb
53 !
54 IMPLICIT NONE
55 !
56 !* 0.1 Declaration of arguments
57 !------------------------
58 !
59 !
60 TYPE(watflux_t), INTENT(INOUT) :: W
61 !
62 !* 0.2 Declaration of local variables
63 ! ------------------------------
64 !
65 REAL :: ZDAT ! current day in the current month
66 REAL :: ZNDAT ! number of days in the current month
67 INTEGER :: IMTH0 ! previous month
68 INTEGER :: IMTH1 ! current month
69 INTEGER :: IMTH2 ! next month
70 INTEGER :: INDAYS ! number of days in KMONTH
71 !
72 INTEGER :: IDELTA
73 !
74 REAL(KIND=JPRB) :: ZHOOK_HANDLE
75 !-------------------------------------------------------------------------------
76 !
77 !* 1. Number of days in a month
78 ! -------------------------
79 !
80 IF (lhook) CALL dr_hook('INTERPOL_TS_WATER_MTH',0,zhook_handle)
81 SELECT CASE (w%TTIME%TDATE%MONTH)
82  CASE(4,6,9,11)
83  indays=30
84  CASE(1,3,5,7:8,10,12)
85  indays=31
86  CASE(2)
87  IF( ((mod(w%TTIME%TDATE%YEAR,4)==0).AND.(mod(w%TTIME%TDATE%YEAR,100)/=0)) .OR. (mod(w%TTIME%TDATE%YEAR,400)==0))THEN
88  indays=29
89  ELSE
90  indays=28
91  ENDIF
92 END SELECT
93 !
94 !
95 !-------------------------------------------------------------------------------
96 !
97 !* 2. TS water Interpolation using previous, current and next month
98 ! -------------------------------------------------------------
99 !
100 zdat = REAL(w%ttime%tdate%day)
101 zndat= REAL(indays)
102 !
103 ! The current month correspond to the indice 2 (or 3 if next month))
104 !
105 IF (w%TTIME%TDATE%MONTH==w%TZTIME%TDATE%MONTH) THEN
106  idelta=0
107 ELSE
108  idelta=1
109 END IF
110 !
111 imth0=1+idelta
112 imth1=2+idelta
113 imth2=3+idelta
114 !
115 IF(w%CINTERPOL_TS=='QUADRA')THEN
116  CALL interpol_quadra(zdat,zndat,w%XTS_MTH(:,imth0),w%XTS_MTH(:,imth1),w%XTS_MTH(:,imth2),w%XTS)
117 ELSEIF(w%CINTERPOL_TS=='LINEAR')THEN
118  CALL interpol_linear(zdat,zndat,w%XTS_MTH(:,imth0),w%XTS_MTH(:,imth1),w%XTS_MTH(:,imth2),w%XTS)
119 ELSEIF(w%CINTERPOL_TS=='UNIF')THEN
120  w%XTS(:) = w%XTS_MTH(:,imth1)
121 ELSE
122  CALL abor1_sfx('INTERPOL_TS_WATER_MTH: interpolation method not supported')
123 ENDIF
124 !
125 IF (lhook) CALL dr_hook('INTERPOL_TS_WATER_MTH',1,zhook_handle)
126 !
127 !-------------------------------------------------------------------------------
128 !
129 END SUBROUTINE interpol_ts_water_mth
subroutine interpol_quadra(PDAT, PNDAT, PVAL0, PVAL1, PVAL2, POUT)
subroutine abor1_sfx(YTEXT)
Definition: abor1_sfx.F90:7
integer, parameter jprb
Definition: parkind1.F90:32
subroutine interpol_ts_water_mth(W)
logical lhook
Definition: yomhook.F90:15
subroutine interpol_linear(PDAT, PNDAT, PVAL0, PVAL1, PVAL2, POUT)