SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
default_ideal_flux.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 default_ideal_flux(KFORCF, KFORCT, PTIMEF, PTIMET, &
7  psfth, psftq, psfco2, &
8  hustartype, pustar, pz0m, palb, &
9  pemis, ptsrad)
10 ! ########################################################################
11 !
12 !!**** *DEFAULT_IDEAL_FLUX* - routine to set default values for the configuration for ISBA FLUX assimilation scheme
13 !!
14 !! PURPOSE
15 !! -------
16 !!
17 !!** METHOD
18 !! ------
19 !!
20 !! EXTERNAL
21 !! --------
22 !!
23 !!
24 !! IMPLICIT ARGUMENTS
25 !! ------------------
26 !!
27 !! REFERENCE
28 !! ---------
29 !!
30 !!
31 !! AUTHOR
32 !! ------
33 !! L. Jarlan *Meteo France*
34 !!
35 !! MODIFICATIONS
36 !! -------------
37 !! Original 02/2005
38 !-------------------------------------------------------------------------------
39 !
40 !* 0. DECLARATIONS
41 ! ------------
42 !
43 USE modd_surf_par, ONLY : xundef
44 USE modd_csts, ONLY : xtt
45 !
46 USE yomhook ,ONLY : lhook, dr_hook
47 USE parkind1 ,ONLY : jprb
48 !
49 IMPLICIT NONE
50 !
51 !* 0.1 Declarations of arguments
52 ! -------------------------
53 INTEGER, INTENT(OUT) :: kforcf
54 INTEGER, INTENT(OUT) :: kforct
55 REAL, DIMENSION(:), INTENT(OUT) :: ptimef
56 REAL, DIMENSION(:), INTENT(OUT) :: ptimet
57 REAL, DIMENSION(:), INTENT(OUT) :: psfth ! hourly data of heat surface flux (W/m2)
58 REAL, DIMENSION(:), INTENT(OUT) :: psftq ! hourly data of water vapor surface flux (kg/m2/s) or (W/m2)
59 REAL, DIMENSION(:), INTENT(OUT) :: psfco2 ! hourly data of CO2 surface flux (kg/m2/s)
60  CHARACTER(LEN=5), INTENT(OUT) :: hustartype ! type of computation for friction
61  ! 'USTAR'
62  ! 'Z0 '
63 REAL, DIMENSION(:), INTENT(OUT) :: pustar ! hourly data of friction (m2/s2)
64 REAL, INTENT(OUT) :: pz0m ! roughness length (m)
65 REAL, INTENT(OUT) :: palb ! albedo (-)
66 REAL, INTENT(OUT) :: pemis ! emissivity (-)
67 REAL, DIMENSION(:),INTENT(OUT) :: ptsrad ! radiative temperature (K)
68 !
69 !* 0.2 declarations of local variables
70 !
71 REAL(KIND=JPRB) :: zhook_handle
72 !
73 !-------------------------------------------------------------------------------
74 IF (lhook) CALL dr_hook('DEFAULT_IDEAL_FLUX',0,zhook_handle)
75 !
76 kforcf = 2.
77 kforct = 2.
78 !
79 ptimef(1) = 0.
80 ptimet(1) = 0.
81 ptimef(2) = xundef
82 ptimet(2) = xundef
83 
84 !
85 !----------------------------------------------------------------------------------
86 !
87 !* 1. HOURLY surface theta flux (NFORC+1 values from 00UTC to 24UTC)
88 ! -------------------------
89 !
90 !* unit: W/m2
91 !
92 psfth(:) = 0.
93 !
94 !----------------------------------------------------------------------------------
95 !
96 !* 2. HOURLY surface vapor mixing ratio flux (NFORC+1 values from 00UTC to 24UTC)
97 ! --------------------------------------
98 !
99 !* unit: kg/m2/s
100 !
101 psftq(:) = 0.
102 !
103 !----------------------------------------------------------------------------------
104 !
105 !* 4. HOURLY surface CO2 flux (NFORC+1 values from 00UTC to 24UTC)
106 ! -----------------------
107 !
108 !* unit: kg/m2/s
109 !
110 psfco2(:) = 0.
111 !
112 !----------------------------------------------------------------------------------
113 !
114 !* 5. Type of definition for friction fluxes
115 ! --------------------------------------
116 !
117 !* HUSTARTYPE = 'Z0 ' ! friction is defined using a roughness length formulation
118 !* = 'USTAR' ! friction is prescribed via the friction velocity u*
119 !
120 hustartype = 'Z0 '
121 !
122 !----------------------------------------------------------------------------------
123 !
124 !* 6. Roughness length (used if XUSTARTYPE = 'Z0 ')
125 ! ----------------
126 !
127 pz0m = 0.01 ! unit in meters
128 !
129 !----------------------------------------------------------------------------------
130 !
131 !* 6. Friction (used if XUSTARTYPE = 'USTAR')
132 ! --------
133 !
134 !* unit: m2/s2
135 !
136 pustar = 0.
137 !
138 !
139 !----------------------------------------------------------------------------------
140 !
141 !* 7. HOURLY surface radiative temperature (NFORC+1 values from 00UTC to 24UTC)
142 ! -------------------------
143 !
144 
145 ptsrad(:) = xtt ! radiative surface temperature, (unit is K)
146 !
147 !----------------------------------------------------------------------------------
148 !
149 !* 8. Radiative fields constant and uniform values
150 ! --------------------------------------------
151 !
152 palb = 0. ! albedo, no unit
153 pemis = 1. ! emissivity, no unit
154 !
155 IF (lhook) CALL dr_hook('DEFAULT_IDEAL_FLUX',1,zhook_handle)
156 !
157 END SUBROUTINE default_ideal_flux
subroutine default_ideal_flux(KFORCF, KFORCT, PTIMEF, PTIMET, PSFTH, PSFTQ, PSFCO2, HUSTARTYPE, PUSTAR, PZ0M, PALB, PEMIS, PTSRAD)