SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_sson.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_sso_n (&
7  u, uss, &
8  hprogram)
9 ! ################################
10 !
11 !!**** *READ_SSO_n* - routine to read a file for
12 !! physiographic data file of model _n
13 !!
14 !! PURPOSE
15 !! -------
16 !! The purpose of this routine is to initialise the
17 !! physiographic data file.
18 !!
19 !!
20 !!** METHOD
21 !! ------
22 !! The data are read in the initial surface file :
23 !! - 2D physiographic data fields
24 !!
25 !! It does not read the grid definition. This should have been
26 !! read already.
27 !!
28 !! EXTERNAL
29 !! --------
30 !!
31 !!
32 !!
33 !! IMPLICIT ARGUMENTS
34 !! ------------------
35 !!
36 !! REFERENCE
37 !! ---------
38 !!
39 !!
40 !! AUTHOR
41 !! ------
42 !! V. Masson *Meteo France*
43 !!
44 !! MODIFICATIONS
45 !! -------------
46 !! Original 01/2003
47 !-------------------------------------------------------------------------------
48 !
49 !* 0. DECLARATIONS
50 ! ------------
51 !
52 !
53 !
54 !
55 !
56 !
57 !
58 USE modd_surf_atm_n, ONLY : surf_atm_t
60 !
62 !
63 USE modd_surf_par, ONLY : xundef
64 !
65 USE yomhook ,ONLY : lhook, dr_hook
66 USE parkind1 ,ONLY : jprb
67 !
68 IMPLICIT NONE
69 !
70 !* 0.1 Declarations of arguments
71 ! -------------------------
72 !
73 !
74 !
75 !
76 TYPE(surf_atm_t), INTENT(INOUT) :: u
77 TYPE(surf_atm_sso_t), INTENT(INOUT) :: uss
78 !
79  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
80 !
81 !* 0.2 Declarations of local variables
82 ! -------------------------------
83 !
84 
85 !
86 INTEGER :: iresp ! Error code after redding
87 !
88  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
89 REAL(KIND=JPRB) :: zhook_handle
90 !
91 !-------------------------------------------------------------------------------
92 !
93 !* 2. Orography :
94 ! ---------
95 !
96 !
97 IF (lhook) CALL dr_hook('READ_SSO_N',0,zhook_handle)
98 IF(.NOT.ASSOCIATED(uss%XAVG_ZS)) ALLOCATE(uss%XAVG_ZS(u%NSIZE_FULL))
99 yrecfm='AVG_ZS'
100  CALL read_surf(&
101  hprogram,yrecfm,uss%XAVG_ZS(:),iresp)
102 !
103 IF(.NOT.ASSOCIATED(uss%XSIL_ZS)) ALLOCATE(uss%XSIL_ZS(u%NSIZE_FULL))
104 yrecfm='SIL_ZS'
105  CALL read_surf(&
106  hprogram,yrecfm,uss%XSIL_ZS(:),iresp)
107 !
108 !
109 !* 3. Subgrid Orography :
110 ! -----------------
111 !
112 !
113 IF(.NOT.ASSOCIATED(uss%XSSO_STDEV)) ALLOCATE(uss%XSSO_STDEV(u%NSIZE_FULL))
114 yrecfm='SSO_STDEV'
115  CALL read_surf(&
116  hprogram,yrecfm,uss%XSSO_STDEV(:),iresp)
117 WHERE (u%XSEA(:) == 1.) uss%XSSO_STDEV(:) = xundef
118 !
119 IF(.NOT.ASSOCIATED(uss%XMIN_ZS)) ALLOCATE(uss%XMIN_ZS(u%NSIZE_FULL))
120 yrecfm='MIN_ZS'
121  CALL read_surf(&
122  hprogram,yrecfm,uss%XMIN_ZS(:),iresp)
123 !
124 IF(.NOT.ASSOCIATED(uss%XMAX_ZS)) ALLOCATE(uss%XMAX_ZS(u%NSIZE_FULL))
125 yrecfm='MAX_ZS'
126  CALL read_surf(&
127  hprogram,yrecfm,uss%XMAX_ZS(:),iresp)
128 !
129 IF(.NOT.ASSOCIATED(uss%XSSO_ANIS)) ALLOCATE(uss%XSSO_ANIS(u%NSIZE_FULL))
130 yrecfm='SSO_ANIS'
131  CALL read_surf(&
132  hprogram,yrecfm,uss%XSSO_ANIS(:),iresp)
133 WHERE (u%XSEA(:) == 1.) uss%XSSO_ANIS(:) = xundef
134 !
135 IF(.NOT.ASSOCIATED(uss%XSSO_DIR)) ALLOCATE(uss%XSSO_DIR(u%NSIZE_FULL))
136 yrecfm='SSO_DIR'
137  CALL read_surf(&
138  hprogram,yrecfm,uss%XSSO_DIR(:),iresp)
139 WHERE (u%XSEA(:) == 1.) uss%XSSO_DIR(:) = xundef
140 !
141 IF(.NOT.ASSOCIATED(uss%XSSO_SLOPE)) ALLOCATE(uss%XSSO_SLOPE(u%NSIZE_FULL))
142 yrecfm='SSO_SLOPE'
143  CALL read_surf(&
144  hprogram,yrecfm,uss%XSSO_SLOPE(:),iresp)
145 WHERE (u%XSEA(:) == 1.) uss%XSSO_SLOPE(:) = xundef
146 !
147 !-------------------------------------------------------------------------------
148 !
149 !* 3. Subgrid Orography roughness:
150 ! ---------------------------
151 !
152 !
153 IF(.NOT.ASSOCIATED(uss%XHO2IP)) ALLOCATE(uss%XHO2IP(u%NSIZE_FULL))
154 yrecfm='HO2IP'
155  CALL read_surf(&
156  hprogram,yrecfm,uss%XHO2IP(:),iresp)
157 WHERE (u%XSEA(:) == 1.) uss%XHO2IP(:) = xundef
158 !
159 IF(.NOT.ASSOCIATED(uss%XHO2JP)) ALLOCATE(uss%XHO2JP(u%NSIZE_FULL))
160 yrecfm='HO2JP'
161  CALL read_surf(&
162  hprogram,yrecfm,uss%XHO2JP(:),iresp)
163 WHERE (u%XSEA(:) == 1.) uss%XHO2JP(:) = xundef
164 !
165 IF(.NOT.ASSOCIATED(uss%XHO2IM)) ALLOCATE(uss%XHO2IM(u%NSIZE_FULL))
166 yrecfm='HO2IM'
167  CALL read_surf(&
168  hprogram,yrecfm,uss%XHO2IM(:),iresp)
169 WHERE (u%XSEA(:) == 1.) uss%XHO2IM(:) = xundef
170 !
171 IF(.NOT.ASSOCIATED(uss%XHO2JM)) ALLOCATE(uss%XHO2JM(u%NSIZE_FULL))
172 yrecfm='HO2JM'
173  CALL read_surf(&
174  hprogram,yrecfm,uss%XHO2JM(:),iresp)
175 WHERE (u%XSEA(:) == 1.) uss%XHO2JM(:) = xundef
176 !
177 IF(.NOT.ASSOCIATED(uss%XAOSIP)) ALLOCATE(uss%XAOSIP(u%NSIZE_FULL))
178 yrecfm='AOSIP'
179  CALL read_surf(&
180  hprogram,yrecfm,uss%XAOSIP(:),iresp)
181 WHERE (u%XSEA(:) == 1.) uss%XAOSIP(:) = xundef
182 !
183 IF(.NOT.ASSOCIATED(uss%XAOSJP)) ALLOCATE(uss%XAOSJP(u%NSIZE_FULL))
184 yrecfm='AOSJP'
185  CALL read_surf(&
186  hprogram,yrecfm,uss%XAOSJP(:),iresp)
187 WHERE (u%XSEA(:) == 1.) uss%XAOSJP(:) = xundef
188 !
189 IF(.NOT.ASSOCIATED(uss%XAOSIM)) ALLOCATE(uss%XAOSIM(u%NSIZE_FULL))
190 yrecfm='AOSIM'
191  CALL read_surf(&
192  hprogram,yrecfm,uss%XAOSIM(:),iresp)
193 WHERE (u%XSEA(:) == 1.) uss%XAOSIM(:) = xundef
194 !
195 IF(.NOT.ASSOCIATED(uss%XAOSJM)) ALLOCATE(uss%XAOSJM(u%NSIZE_FULL))
196 yrecfm='AOSJM'
197  CALL read_surf(&
198  hprogram,yrecfm,uss%XAOSJM(:),iresp)
199 WHERE (u%XSEA(:) == 1.) uss%XAOSJM(:) = xundef
200 IF (lhook) CALL dr_hook('READ_SSO_N',1,zhook_handle)
201 !
202 !
203 !-------------------------------------------------------------------------------
204 !
205 END SUBROUTINE read_sso_n
subroutine read_sso_n(U, USS, HPROGRAM)
Definition: read_sson.F90:6