SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
writesurf_flake_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 writesurf_flake_sbl_n (DGU, U, &
7  f, fsb, &
8  hprogram,hwrite)
9 ! ####################################
10 !
11 !!**** *WRITE_FLAKE_n* - writes FLAKE fields
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 avoid write of XUNDEF fields
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 !
44 !
45 !
46 !
47 !
48 !
50 USE modd_surf_atm_n, ONLY : surf_atm_t
51 !
52 USE modd_flake_n, ONLY : flake_t
53 USE modd_flake_sbl_n, ONLY : flake_sbl_t
54 !
56 !
57 !
58 USE yomhook ,ONLY : lhook, dr_hook
59 USE parkind1 ,ONLY : jprb
60 !
61 IMPLICIT NONE
62 !
63 !* 0.1 Declarations of arguments
64 ! -------------------------
65 !
66 !
67 !
68 TYPE(diag_surf_atm_t), INTENT(INOUT) :: dgu
69 TYPE(surf_atm_t), INTENT(INOUT) :: u
70 !
71 TYPE(flake_t), INTENT(INOUT) :: f
72 TYPE(flake_sbl_t), INTENT(INOUT) :: fsb
73 !
74  CHARACTER(LEN=6), INTENT(IN) :: hprogram ! program calling
75  CHARACTER(LEN=3), INTENT(IN) :: hwrite ! 'PREP' : does not write SBL XUNDEF fields
76 ! ! 'ALL' : all fields are written
77 !* 0.2 Declarations of local variables
78 ! -------------------------------
79 !
80 INTEGER :: iresp ! IRESP : return-code if a problem appears
81  CHARACTER(LEN=12) :: yrecfm ! Name of the article to be read
82  CHARACTER(LEN=100):: ycomment ! Comment string
83 !
84 INTEGER :: jlayer ! loop counter on layers
85 REAL(KIND=JPRB) :: zhook_handle
86 !-------------------------------------------------------------------------------
87 !
88 !* 1. Prognostic fields:
89 ! -----------------
90 !
91 !* flag to define if SBL is computed
92 !
93 IF (lhook) CALL dr_hook('WRITESURF_FLAKE_SBL_N',0,zhook_handle)
94 yrecfm='WAT_SBL'
95 ycomment='flag to use SBL levels'
96  CALL write_surf(dgu, u, &
97  hprogram,yrecfm,f%LSBL,iresp,hcomment=ycomment)
98 !
99 IF (.NOT. f%LSBL .AND. lhook) CALL dr_hook('WRITESURF_FLAKE_SBL_N',1,zhook_handle)
100 IF (.NOT. f%LSBL) RETURN
101 !
102 !* number of levels
103 !
104 yrecfm='WAT_SBL_LVL'
105 ycomment='number of SBL levels'
106  CALL write_surf(dgu, u, &
107  hprogram,yrecfm,fsb%NLVL,iresp,hcomment=ycomment)
108 !
109 !* altitudes
110 !
111 DO jlayer=1,fsb%NLVL
112  WRITE(yrecfm,'(A9,I2.2,A1)') 'WAT_SBL_Z',jlayer,' '
113  ycomment='altitudes of SBL levels (m)'
114  CALL write_surf(dgu, u, &
115  hprogram,yrecfm,fsb%XZ(:,jlayer),iresp,hcomment=ycomment)
116 END DO
117 !
118 IF (hwrite/='PRE') THEN
119  !
120  !* wind in SBL
121  !
122  DO jlayer=1,fsb%NLVL
123  WRITE(yrecfm,'(A9,I2.2,A1)') 'WAT_SBL_U',jlayer,' '
124  ycomment='wind at SBL levels (m/s)'
125  CALL write_surf(dgu, u, &
126  hprogram,yrecfm,fsb%XU(:,jlayer),iresp,hcomment=ycomment)
127  END DO
128  !
129  !* temperature in SBL
130  !
131  DO jlayer=1,fsb%NLVL
132  WRITE(yrecfm,'(A9,I2.2,A1)') 'WAT_SBL_T',jlayer,' '
133  ycomment='temperature at SBL levels (K)'
134  CALL write_surf(dgu, u, &
135  hprogram,yrecfm,fsb%XT(:,jlayer),iresp,hcomment=ycomment)
136  END DO
137  !
138  !* humidity in SBL
139  !
140  DO jlayer=1,fsb%NLVL
141  WRITE(yrecfm,'(A9,I2.2,A1)') 'WAT_SBL_Q',jlayer,' '
142  ycomment='humidity at SBL levels (kg/m3)'
143  CALL write_surf(dgu, u, &
144  hprogram,yrecfm,fsb%XQ(:,jlayer),iresp,hcomment=ycomment)
145  END DO
146  !
147  !* Tke in SBL
148  !
149  DO jlayer=1,fsb%NLVL
150  WRITE(yrecfm,'(A9,I2.2,A1)') 'WAT_SBL_E',jlayer,' '
151  ycomment='Tke at SBL levels (m2/s2)'
152  CALL write_surf(dgu, u, &
153  hprogram,yrecfm,fsb%XTKE(:,jlayer),iresp,hcomment=ycomment)
154  END DO
155  !
156  !* Monin-Obhukov length
157  !
158  yrecfm='WAT_SBL_LMO '
159  CALL write_surf(dgu, u, &
160  hprogram,yrecfm,fsb%XLMO(:),iresp,hcomment=ycomment)
161  !
162  !* Air pressure in SBL
163  !
164  DO jlayer=1,fsb%NLVL
165  WRITE(yrecfm,'(A9,I2.2,A1)') 'WAT_SBL_P',jlayer,' '
166  ycomment='Pressure at SBL levels (Pa)'
167  CALL write_surf(dgu, u, &
168  hprogram,yrecfm,fsb%XP(:,jlayer),iresp,hcomment=ycomment)
169  END DO
170  !
171 ENDIF
172 !
173 IF (lhook) CALL dr_hook('WRITESURF_FLAKE_SBL_N',1,zhook_handle)
174 !
175 !
176 !-------------------------------------------------------------------------------
177 !
178 END SUBROUTINE writesurf_flake_sbl_n
subroutine writesurf_flake_sbl_n(DGU, U, F, FSB, HPROGRAM, HWRITE)