SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_watfluxn.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 read_watflux_n (DTCO, U, W, &
7  hprogram)
8 ! #########################################
9 !
10 !!**** *READ_WATFLUX_n* - reads WATFLUX variables
11 !!
12 !!
13 !! PURPOSE
14 !! -------
15 !!
16 !!** METHOD
17 !! ------
18 !!
19 !! EXTERNAL
20 !! --------
21 !!
22 !!
23 !! IMPLICIT ARGUMENTS
24 !! ------------------
25 !!
26 !! REFERENCE
27 !! ---------
28 !!
29 !!
30 !! AUTHOR
31 !! ------
32 !! V. Masson *Meteo France*
33 !!
34 !! MODIFICATIONS
35 !! -------------
36 !! Original 01/2003
37 !-------------------------------------------------------------------------------
38 !
39 !* 0. DECLARATIONS
40 ! ------------
41 !
42 !
43 !
44 !
45 !
47 USE modd_surf_atm_n, ONLY : surf_atm_t
48 USE modd_watflux_n, ONLY : watflux_t
49 !
51 USE modi_interpol_ts_water_mth
52 !
53 !
54 USE yomhook ,ONLY : lhook, dr_hook
55 USE parkind1 ,ONLY : jprb
56 !
57 USE modi_get_type_dim_n
58 !
59 IMPLICIT NONE
60 !
61 !* 0.1 Declarations of arguments
62 ! -------------------------
63 !
64 !
65 TYPE(data_cover_t), INTENT(INOUT) :: dtco
66 TYPE(surf_atm_t), INTENT(INOUT) :: u
67 TYPE(watflux_t), INTENT(INOUT) :: w
68 !
69  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
70 !
71 !
72 !* 0.2 Declarations of local variables
73 ! -------------------------------
74 !
75 INTEGER :: jmth, inmth
76  CHARACTER(LEN=2 ) :: ymth
77 !
78 INTEGER :: ilu ! 1D physical dimension
79 !
80 INTEGER :: iresp ! Error code after redding
81 !
82  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
83 REAL(KIND=JPRB) :: zhook_handle
84 !
85 !-------------------------------------------------------------------------------
86 !
87 !* 1D physical dimension
88 !
89 IF (lhook) CALL dr_hook('READ_WATFLUX_N',0,zhook_handle)
90 yrecfm='SIZE_WATER'
91  CALL get_type_dim_n(dtco, u, &
92  'WATER ',ilu)
93 !
94 !* 3. Prognostic fields:
95 ! -----------------
96 !
97 !* water temperature
98 !
99 ALLOCATE(w%XTS(ilu))
100 !
101 IF(w%LINTERPOL_TS)THEN
102 !
103 ! Initialize current Month
104  w%TZTIME%TDATE%YEAR = w%TTIME%TDATE%YEAR
105  w%TZTIME%TDATE%MONTH = w%TTIME%TDATE%MONTH
106  w%TZTIME%TDATE%DAY = w%TTIME%TDATE%DAY
107  w%TZTIME%TIME = w%TTIME%TIME
108 
109 ! Precedent, Current, Next, and Second-next Monthly SST
110  inmth=4
111 !
112  ALLOCATE(w%XTS_MTH(SIZE(w%XTS),inmth))
113  DO jmth=1,inmth
114  WRITE(ymth,'(I2)') (jmth-1)
115  yrecfm='TS_WATER'//adjustl(ymth(:len_trim(ymth)))
116  CALL read_surf(&
117  hprogram,yrecfm,w%XTS_MTH(:,jmth),iresp)
118  ENDDO
119 !
120  CALL interpol_ts_water_mth(w, &
121  w%TTIME%TDATE%YEAR,w%TTIME%TDATE%MONTH,w%TTIME%TDATE%DAY,w%XTS)
122 !
123 ELSE
124 !
125  ALLOCATE(w%XTS_MTH(0,0))
126 !
127  yrecfm='TS_WATER'
128  CALL read_surf(&
129  hprogram,yrecfm,w%XTS(:),iresp)
130 !
131 ENDIF
132 !
133 !
134 !-------------------------------------------------------------------------------
135 !
136 !* 4. Semi-prognostic fields:
137 ! ----------------------
138 !
139 !* roughness length
140 !
141 ALLOCATE(w%XZ0(ilu))
142 yrecfm='Z0WATER'
143 w%XZ0(:) = 0.001
144  CALL read_surf(&
145  hprogram,yrecfm,w%XZ0(:),iresp)
146 IF (lhook) CALL dr_hook('READ_WATFLUX_N',1,zhook_handle)
147 !
148 !-------------------------------------------------------------------------------
149 
150 !
151 END SUBROUTINE read_watflux_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine read_watflux_n(DTCO, U, W, HPROGRAM)
subroutine interpol_ts_water_mth(W, KYEAR, KMONTH, KDAY, PTS)