SURFEX v8.1
General documentation of Surfex
diag_surf_atmn.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 diag_surf_atm_n (YSC, HPROGRAM)
7 ! #################################################################################
8 !
9 !!**** *DIAG_SURF_ATM_n * - Chooses the surface schemes for diagnostics
10 !!
11 !! PURPOSE
12 !! -------
13 !
14 !!** METHOD
15 !! ------
16 !!
17 !! REFERENCE
18 !! ---------
19 !!
20 !!
21 !! AUTHOR
22 !! ------
23 !! V. Masson
24 !!
25 !! MODIFICATIONS
26 !! -------------
27 !! Original 01/2004
28 !! Modified 01/2006 : sea flux parameterization.
29 !! Modified 08/2008 : cumulated fluxes
30 ! B. decharme 04/2013 : Add EVAP and SUBL diag
31 !!------------------------------------------------------------------
32 !
33 USE modd_surfex_n, ONLY : surfex_t
34 !
35 USE modd_surf_conf, ONLY : cprogname
36 USE modd_data_cover_par, ONLY : ntilesfc
37 !
38 USE modi_diag_nature_n
39 USE modi_diag_sea_n
40 USE modi_diag_inland_water_n
41 USE modi_diag_town_n
42 USE modi_average_diag
43 !
44 USE modi_minzs_vert_shift
45 !
46 !
47 USE yomhook ,ONLY : lhook, dr_hook
48 USE parkind1 ,ONLY : jprb
49 !
50 IMPLICIT NONE
51 !
52 !* 0.1 declarations of arguments
53 !
54 TYPE(surfex_t), INTENT(INOUT) :: YSC
55 !
56  CHARACTER(LEN=6), INTENT(IN) :: HPROGRAM ! program calling surf. schemes
57 !
58 !
59 !* 0.2 declarations of local variables
60 !
61 INTEGER :: JTILE ! loop on type of surface
62 LOGICAL :: GNATURE, GTOWN, GWATER, GSEA ! .T. if the corresponding surface is represented
63 INTEGER :: JSW ! number of spectral whort wave bands
64 !
65 REAL, DIMENSION(SIZE(YSC%U%XSEA),NTILESFC) :: ZFRAC_TILE! fraction of each tile
66 REAL(KIND=JPRB) :: ZHOOK_HANDLE
67 !-------------------------------------------------------------------------------------
68 ! Preliminaries: Tile related operations
69 !-------------------------------------------------------------------------------------
70 !
71 IF (lhook) CALL dr_hook('DIAG_SURF_ATM_N',0,zhook_handle)
72 cprogname = hprogram
73 !
74 ! FLAGS for the various surfaces:
75 !
76 gsea = ysc%U%NDIM_SEA >0
77 gwater = ysc%U%NDIM_WATER >0
78 gtown = ysc%U%NDIM_TOWN >0
79 gnature = ysc%U%NDIM_NATURE >0
80 !
81 ! Tile counter:
82 !
83 jtile = 0
84 !
85 ! Fractions for each tile:
86 !
87 zfrac_tile(:,:) = 0.0
88 !
89 ! Number of spectral short wave bands for detailed radiation budget
90 jsw = SIZE(ysc%DUP%AL(1)%XSWBD,2)
91 !
92 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
93 ! SEA Tile calculations:
94 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
95 !
96 ! first, pack vector...then call ALMA routine
97 !
98 jtile = jtile + 1
99 !
100 IF(gsea)THEN
101 !
102  zfrac_tile(:,jtile) = ysc%U%XSEA(:)
103 !
104  CALL diag_sea_n(ysc%DLO, ysc%DL, ysc%DLC, ysc%SM%SD, &
105  ysc%U%CSEA, hprogram, ysc%DUP%AL(1), ysc%DUPC%AL(1), ysc%U%NR_SEA)
106 !
107 ENDIF
108 !
109 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
110 ! INLAND WATER Tile calculations:
111 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
112 !
113 jtile = jtile + 1
114 !
115 IF(gwater)THEN
116 !
117  zfrac_tile(:,jtile) = ysc%U%XWATER(:)
118 !
119  CALL diag_inland_water_n(ysc%DLO, ysc%DL, ysc%DLC, ysc%FM, ysc%WM, &
120  ysc%U%CWATER, hprogram, ysc%DUP%AL(2), ysc%DUPC%AL(2), ysc%U%NR_WATER)
121 !
122 ENDIF
123 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
124 ! NATURAL SURFACE Tile calculations:
125 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
126 !
127 jtile = jtile + 1
128 !
129 IF(gnature)THEN
130 !
131  zfrac_tile(:,jtile) = ysc%U%XNATURE(:)
132 !
133  CALL diag_nature_n(ysc%DLO, ysc%DL, ysc%DLC, ysc%IM%ID, &
134  ysc%U%CNATURE, hprogram, ysc%DUP%AL(3), ysc%DUPC%AL(3), ysc%U%NR_NATURE)
135 !
136 ENDIF
137 !
138 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
139 ! URBAN Tile calculations:
140 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
141 !
142 jtile = jtile + 1
143 !
144 IF(gtown)THEN
145 !
146  zfrac_tile(:,jtile) = ysc%U%XTOWN(:)
147 !
148  CALL diag_town_n(ysc%DLO, ysc%DL, ysc%DLC, ysc%TM%TD, &
149  ysc%U%CTOWN, hprogram, ysc%DUP%AL(4), ysc%DUPC%AL(4), ysc%U%NR_TOWN)
150 !
151 ENDIF
152 !
153 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
154 ! Grid box average fluxes/properties:
155 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
156 !
157  CALL average_diag(zfrac_tile, ysc%DUO, ysc%DU, ysc%DUP, ysc%DUC, ysc%DUPC)
158 !
159 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
160 ! Quantities at 2 meters above the minimum orography of the grid mesh
161 ! - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
162 !
163 IF (ysc%DUO%L2M_MIN_ZS) CALL get_2m
164 !
165 IF (lhook) CALL dr_hook('DIAG_SURF_ATM_N',1,zhook_handle)
166 CONTAINS
167 !=======================================================================================
168 SUBROUTINE get_2m
169 !
170 REAL, DIMENSION(SIZE(YSC%U%XSEA)) :: ZPS ! surface air pressure
171 REAL, DIMENSION(SIZE(YSC%U%XSEA)) :: ZRHOA ! surface air density
172 REAL(KIND=JPRB) :: ZHOOK_HANDLE
173 !
174 IF (lhook) CALL dr_hook('DIAG_SURF_ATM_n:GET_2M',0,zhook_handle)
175 !
176  CALL minzs_vert_shift(ysc%DU, ysc%U%XZS, ysc%USS%XMIN_ZS, zps, zrhoa)
177 ysc%DU%XHU2M_MIN_ZS = ysc%DU%XHU2M
178 !
179 IF (lhook) CALL dr_hook('DIAG_SURF_ATM_n:GET_2M',1,zhook_handle)
180 !
181 END SUBROUTINE get_2m
182 !
183 !=======================================================================================
184 END SUBROUTINE diag_surf_atm_n
subroutine minzs_vert_shift(D, PZS_MOY, PZS_MIN, PPS_MIN, PRHOA_2M_MIN)
subroutine diag_surf_atm_n(YSC, HPROGRAM)
subroutine diag_nature_n(DLO, DL, DLC, ID, HNATURE, HPROGRAM, DUP, DUPC, KMASK)
Definition: diag_naturen.F90:8
subroutine average_diag(PFRAC_TILE, DGO, D, ND, DC, NDC)
Definition: average_diag.F90:7
subroutine diag_sea_n(DLO, DL, DLC, SD, HSEA, HPROGRAM, DUP, DUPC, KMASK)
Definition: diag_sean.F90:7
integer, parameter jprb
Definition: parkind1.F90:32
character(len=6) cprogname
subroutine get_2m
logical lhook
Definition: yomhook.F90:15
subroutine diag_inland_water_n(DLO, DL, DLC, FM, WM, HWATER, HPROGRAM, DUP, DUPC, KMASK)
subroutine diag_town_n(DLO, DL, DLC, TD, HTOWN, HPROGRAM, DUP, DUPC, KMASK)
Definition: diag_townn.F90:7