SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
read_seaflux_sbln.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_seaflux_sbl_n (DTCO, S, SSB, U, &
7  hprogram)
8 ! #########################################
9 !
10 !!**** *READ_SEAFLUX_SBL_n* - reads SEAFLUX fields
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 !! E. Martin 01/2012 Add LSBL_COLD_START
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
44 !
45 !
47 USE modd_seaflux_n, ONLY : seaflux_t
49 USE modd_surf_atm_n, ONLY : surf_atm_t
50 !
51 USE modd_surf_par, ONLY : xundef
52 !
54 USE modi_canopy_grid
55 USE modi_get_type_dim_n
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 TYPE(data_cover_t), INTENT(INOUT) :: dtco
67 TYPE(seaflux_t), INTENT(INOUT) :: s
68 TYPE(seaflux_sbl_t), INTENT(INOUT) :: ssb
69 TYPE(surf_atm_t), INTENT(INOUT) :: u
70 !
71  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! calling program
72 !
73 !
74 !* 0.2 Declarations of local variables
75 ! -------------------------------
76 !
77 !
78  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
79  CHARACTER(LEN=3) :: yread
80 INTEGER :: ilu ! 1D physical dimension
81 INTEGER :: iresp ! Error code after redding
82 INTEGER :: jlayer ! loop counter on layers
83 INTEGER :: iversion, ibugfix
84 REAL(KIND=JPRB) :: zhook_handle
85 !
86 !-------------------------------------------------------------------------------
87 !
88 !* 1D physical dimension
89 !
90 IF (lhook) CALL dr_hook('READ_SEAFLUX_SBL_N',0,zhook_handle)
91  CALL get_type_dim_n(dtco, u, &
92  'SEA ',ilu)
93 !
94 yrecfm='VERSION'
95  CALL read_surf(&
96  hprogram,yrecfm,iversion,iresp)
97 !
98 yrecfm='BUG'
99  CALL read_surf(&
100  hprogram,yrecfm,ibugfix,iresp)
101 !
102 !* flag to use or not SBL levels
103 !
104 yrecfm='SEA_SBL'
105  CALL read_surf(&
106  hprogram,yrecfm,s%LSBL,iresp)
107 !
108 IF (.NOT.s%LSBL) THEN
109  ALLOCATE(ssb%XZ (0,0))
110  ALLOCATE(ssb%XU (0,0))
111  ALLOCATE(ssb%XT (0,0))
112  ALLOCATE(ssb%XQ (0,0))
113  ALLOCATE(ssb%XTKE(0,0))
114  ALLOCATE(ssb%XLMO(0) )
115  ALLOCATE(ssb%XP (0,0))
116  ALLOCATE(ssb%XDZ (0,0))
117  ALLOCATE(ssb%XZF (0,0))
118  ALLOCATE(ssb%XDZF(0,0))
119  IF (lhook) CALL dr_hook('READ_SEAFLUX_SBL_N',1,zhook_handle)
120  RETURN
121 ENDIF
122 !
123 !* number of vertical levels
124 !
125 yrecfm='SEA_SBL_LVL'
126  CALL read_surf(&
127  hprogram,yrecfm,ssb%NLVL,iresp)
128 !
129 !* 2. Prognostic fields:
130 ! -----------------
131 !
132 !* altitudes
133 !
134 ALLOCATE(ssb%XZ(ilu,ssb%NLVL))
135 !
136 DO jlayer=1,ssb%NLVL
137  WRITE(yrecfm,'(A9,I2.2,A1)') 'SEA_SBL_Z',jlayer,' '
138  CALL read_surf(&
139  hprogram,yrecfm,ssb%XZ(:,jlayer),iresp)
140 END DO
141 !
142 ALLOCATE(ssb%XU (ilu,ssb%NLVL))
143 ALLOCATE(ssb%XT (ilu,ssb%NLVL))
144 ALLOCATE(ssb%XQ (ilu,ssb%NLVL))
145 ALLOCATE(ssb%XTKE(ilu,ssb%NLVL))
146 ALLOCATE(ssb%XLMO(ilu) )
147 ALLOCATE(ssb%XP (ilu,ssb%NLVL))
148 !
149 IF (iversion>7 .OR. iversion==7 .AND.ibugfix>=2) THEN
150  yrecfm='STORAGETYPE'
151  CALL read_surf(&
152  hprogram,yrecfm,yread,iresp)
153 ELSE
154  yread = 'ALL'
155 ENDIF
156 !
157 IF(yread=='ALL') THEN
158  !
159  !* wind in SBL
160  DO jlayer=1,ssb%NLVL
161  WRITE(yrecfm,'(A9,I2.2,A1)') 'SEA_SBL_U',jlayer,' '
162  CALL read_surf(&
163  hprogram,yrecfm,ssb%XU(:,jlayer),iresp)
164  END DO
165  !
166  !* theta in SBL
167  DO jlayer=1,ssb%NLVL
168  WRITE(yrecfm,'(A9,I2.2,A1)') 'SEA_SBL_T',jlayer,' '
169  CALL read_surf(&
170  hprogram,yrecfm,ssb%XT(:,jlayer),iresp)
171  END DO
172  !
173  !* humidity in SBL
174  DO jlayer=1,ssb%NLVL
175  WRITE(yrecfm,'(A9,I2.2,A1)') 'SEA_SBL_Q',jlayer,' '
176  CALL read_surf(&
177  hprogram,yrecfm,ssb%XQ(:,jlayer),iresp)
178  END DO
179  !
180  !* Tke in SBL
181  DO jlayer=1,ssb%NLVL
182  WRITE(yrecfm,'(A9,I2.2,A1)') 'SEA_SBL_E',jlayer,' '
183  CALL read_surf(&
184  hprogram,yrecfm,ssb%XTKE(:,jlayer),iresp)
185  END DO
186  !
187  !* Monin-Obhukov length
188  yrecfm='SEA_SBL_LMO '
189  CALL read_surf(&
190  hprogram,yrecfm,ssb%XLMO(:),iresp)
191  !
192  !* Pressure
193  DO jlayer=1,ssb%NLVL
194  WRITE(yrecfm,'(A9,I2.2,A1)') 'SEA_SBL_P',jlayer,' '
195  CALL read_surf(&
196  hprogram,yrecfm,ssb%XP(:,jlayer),iresp)
197  END DO
198  !
199 ELSE
200  ssb%XU (:,:) = xundef
201  ssb%XT (:,:) = xundef
202  ssb%XQ (:,:) = xundef
203  ssb%XTKE(:,:) = xundef
204  ssb%XLMO(:) = xundef
205  ssb%XP (:,:) = xundef
206 ENDIF
207 !
208 !
209 !* Grid characteristics
210 !
211 !
212 ! --------------------------------- XZ(k+1) XDZ(k+1)
213 ! ^
214 ! |
215 ! |
216 ! - - - - - - - - - - - - - - - - - XZf(k+1) | XDZf(k+1)
217 ! ^ |
218 ! | |
219 ! --------------------------------- XZ(k), XU, XT, XQ, XTKE | XDZ(k) V
220 ! | ^
221 ! - - - - - - - - - - - - - - - - - XZf(k) V | XDZf(k)
222 ! --------------------------------- XZ(k-1) XDZ(k-1) V
223 ! - - - - - - - - - - - - - - - - - XZf(k-1)
224 !
225 ALLOCATE(ssb%XDZ (ilu,ssb%NLVL))
226 ALLOCATE(ssb%XZF (ilu,ssb%NLVL))
227 ALLOCATE(ssb%XDZF(ilu,ssb%NLVL))
228  CALL canopy_grid(ilu,ssb%NLVL,ssb%XZ,ssb%XZF,ssb%XDZ,ssb%XDZF)
229 !
230 IF (lhook) CALL dr_hook('READ_SEAFLUX_SBL_N',1,zhook_handle)
231 !
232 !-------------------------------------------------------------------------------
233 !
234 END SUBROUTINE read_seaflux_sbl_n
subroutine get_type_dim_n(DTCO, U, HTYPE, KDIM)
subroutine read_seaflux_sbl_n(DTCO, S, SSB, U, HPROGRAM)
subroutine canopy_grid(KI, KLVL, PZ, PZF, PDZ, PDZF)
Definition: canopy_grid.F90:6