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