SURFEX  V8_0
Surfex V8_0 release
 All Classes Files Functions Variables
ch_init_dep_isban.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 ch_init_dep_isba_n (CHI, DTCO, I, &
7  kch,kluout,klu)
8 !! ##################################################
9 !!
10 !!*** *CH_INIT_DEP_ISBA_n*
11 !!
12 !! PURPOSE
13 !! -------
14 ! The purpose of this subroutine is to calculate the surface flux
15 ! (emission or deposition) for the chemical (=scalar) variable
16 !!
17 !!** METHOD
18 !! ------
19 !! The surface flux will be calculated using an exchange velocity
20 !! and a surface mixing ratio for each species:
21 !! Flux = v_exchange * ( C(first model level) )
22 !! Exchange velocity and surface concentration will be read from
23 !! the general purpose input file, or,
24 !! if CCH_DRY_DEP = "WES89", the Wesley method will be used
25 !! to calculate the dry deposition velocities. The wesely code
26 !! has been separate into four subroutines: ch_teb_depn.f90 for town area;
27 !! ch_water_depn.f90 for inland water; ch_sea_depn.f90 for sea and
28 !! ch_isba_depn.f90 for nature area.
29 !!
30 !! information read from the input file:
31 !! surface values SURFVALU
32 !! exchange velocities EXCHGVEL (non-Wesley)
33 !!
34 !! in addition for Wesley:
35 !! chemical molecular diffusivity MASS_MOL
36 !! molecular reactivity factor REA_FACT
37 !! surface resistance SURF_RES
38 !! molecular effective Henry constant HENRY_SP
39 !!
40 !!
41 !! REFERENCE
42 !! ---------
43 !!
44 !! AUTHOR
45 !! ------
46 !! K. Suhre *Laboratoire d'Aerologie*
47 !!
48 !! MODIFICATIONS
49 !! -------------
50 !! Original 17/11/95
51 !! 05/08/96 (K. Suhre) restructured
52 !! 19/02/98 (P. Tulet) add explicit dry deposition for chemical species
53 !! 11/08/98 (N. Asencio) add parallel code
54 !! 29/03/99 (K. Suhre) add IKB = MIN(2,SIZE(PSVT,3))
55 !! so that this subroutine can be called by the box model
56 !! 16/01/01 (P. Tulet) restructured
57 !! 18/01/01 (P. Tulet) add patch vegetative class, town and water/sea
58 !! for friction velocity and aerodynamical resistance
59 !! 18/07/03 (P. Tulet) surface externalisation
60 !!
61 !!
62 !! EXTERNAL
63 !! --------
64 !
65 !
66 USE modd_ch_isba_n, ONLY : ch_isba_t
68 USE modd_isba_n, ONLY : isba_t
69 !
70 USE modi_ch_open_inputb ! open the general purpose ASCII input file
71 USE modi_convert_cover_ch_isba
72 !
73 USE modd_ch_isba, ONLY: xrcclayso2, xrcclayo3, xrcsandso2, xrcsando3, &
74  xrcsnowso2, xrcsnowo3, xlandrext
75 USE modd_ch_surf
76 USE modd_surf_par, ONLY : xundef
77 !!
78 !! IMPLICIT ARGUMENTS
79 !! ------------------
80 !-------------------------------------------------------------------------------
81 !
82 !* 0. DECLARATIONS
83 ! ------------
84 !
85 USE yomhook ,ONLY : lhook, dr_hook
86 USE parkind1 ,ONLY : jprb
87 !
88 IMPLICIT NONE
89 !
90 !* 0.1 declarations of arguments
91 !
92 TYPE(ch_isba_t), INTENT(INOUT) :: chi
93 TYPE(data_cover_t), INTENT(INOUT) :: dtco
94 TYPE(isba_t), INTENT(INOUT) :: i
95 !
96 INTEGER, INTENT(IN) :: kch ! chemistry input file
97 INTEGER, INTENT(IN) :: kluout ! output listing channel
98 INTEGER, INTENT(IN) :: klu ! number of points
99 !
100 !* 0.2 declarations of local variables
101 !
102  CHARACTER(LEN=40) :: yformat
103 ! format for input
104  CHARACTER(LEN=40) :: youtformat = '(A32,2E15.5)'
105 ! format for output
106 INTEGER :: iresis ! number of chemical reactivity factor to be read
107  CHARACTER(LEN=40), DIMENSION(:), ALLOCATABLE :: yresisname !resistance name
108 REAL , DIMENSION(:), ALLOCATABLE :: zresisval
109 ! chemical reactivity factor value
110 !
111 INTEGER :: ji, jnreal ! loop control variables
112 REAL(KIND=JPRB) :: zhook_handle
113 !
114 !=============================================================================
115 !
116  !
117  ! 1. Default values
118  !
119  IF (lhook) CALL dr_hook('CH_INIT_DEP_ISBA_N',0,zhook_handle)
120  xrcclayso2 = xundef
121  xrcclayo3 = xundef
122  xrcsandso2 = xundef
123  xrcsando3 = xundef
124  xrcsnowso2 = xundef
125  xrcsnowo3 = xundef
126  xlandrext = xundef
127  !
128  !-----------------------------------------------------------------------------
129  !
130  !
131  IF (chi%CCH_DRY_DEP == "WES89") THEN
132  !
133  !* 2. Physiographic fields
134  !
135  ALLOCATE(chi%XSOILRC_SO2(klu,i%NPATCH))
136  ALLOCATE(chi%XSOILRC_O3(klu,i%NPATCH))
137 
138  CALL convert_cover_ch_isba(dtco, &
139  i%XCOVER,i%LCOVER,chi%XSOILRC_SO2,chi%XSOILRC_O3)
140  !
141  !---------------------------------------------------------------------------
142  !
143  !
144  !* 3. read surface resistance SURF_RES
145  !
146  ALLOCATE(chi%XDEP(klu,chi%SVI%NBEQ,i%NPATCH))
147  !
148 !$OMP SINGLE
149  ! open input file
150  WRITE(kluout,*) &
151  "CH_INIT_DEP_ISBA_n: reading reactivity factor "
152  CALL ch_open_inputb("SURF_RES", kch, kluout)
153  !
154  ! read number of input surface resistance IRESIS
155  READ(kch, *) iresis
156  WRITE(kluout,*) "number of reactivity factor : ", iresis
157  !
158  ! read data input format
159  READ(kch,"(A)") yformat
160  WRITE(kluout,*) "input format is: ", yformat
161 !$OMP END SINGLE COPYPRIVATE(IRESIS,YFORMAT)
162  !
163  ! allocate fields
164  ALLOCATE(yresisname(iresis))
165  ALLOCATE(zresisval(iresis))
166  !
167 !$OMP SINGLE
168  ! read reactivity factor
169  DO ji = 1, iresis
170  READ(kch,yformat) yresisname(ji), zresisval(ji)
171  WRITE(kluout,yformat) yresisname(ji), zresisval(ji)
172  END DO
173 !$OMP END SINGLE COPYPRIVATE(YRESISNAME,ZRESISVAL)
174 !
175  ! close file
176  DO jnreal = 1, iresis
177  IF ('LANDREXT'== yresisname(jnreal) (1:8)) xlandrext = zresisval(jnreal)
178  IF ('RCSANDSO2'== yresisname(jnreal) (1:9)) xrcsandso2 = zresisval(jnreal)
179  IF ('RCSANDO3'== yresisname(jnreal) (1:8)) xrcsando3 = zresisval(jnreal)
180  IF ('RCCLAYSO2'== yresisname(jnreal) (1:9)) xrcclayso2 = zresisval(jnreal)
181  IF ('RCCLAYO3'== yresisname(jnreal) (1:8)) xrcclayo3 = zresisval(jnreal)
182  IF ('RCSNOWSO2'== yresisname(jnreal) (1:9)) xrcsnowso2 = zresisval(jnreal)
183  IF ('RCSNOWO3'== yresisname(jnreal) (1:8)) xrcsnowo3 = zresisval(jnreal)
184  END DO
185  !
186  WRITE(kluout,'(A)') '----------------------------------------------------'
187  WRITE(kluout,'(A)') 'SURF_RES'
188  WRITE(kluout,'(A)') 'surface resistances (s/m)'
189  WRITE(kluout,'(I4)') 7
190  WRITE(kluout,'(A)') youtformat
191  WRITE(kluout,youtformat) 'LANDREXT', xlandrext
192  WRITE(kluout,youtformat) 'RCSANDSO2', xrcsandso2
193  WRITE(kluout,youtformat) 'RCSANDO3', xrcsando3
194  WRITE(kluout,youtformat) 'RCCLAYSO2', xrcclayso2
195  WRITE(kluout,youtformat) 'RCCLAYO3', xrcclayo3
196  WRITE(kluout,youtformat) 'RCSNOWSO2', xrcsnowso2
197  WRITE(kluout,youtformat) 'RCSNOWO3', xrcsnowo3
198  !
199  DEALLOCATE(yresisname)
200  DEALLOCATE(zresisval)
201  ELSE
202  ALLOCATE(chi%XDEP(0,0,0))
203  END IF
204 IF (lhook) CALL dr_hook('CH_INIT_DEP_ISBA_N',1,zhook_handle)
205  !
206  !=============================================================================
207  !
208 END SUBROUTINE ch_init_dep_isba_n
subroutine ch_init_dep_isba_n(CHI, DTCO, I, KCH, KLUOUT, KLU)
subroutine convert_cover_ch_isba(DTCO, PCOVER, OCOVER, PSOILRC_SO2, PSOILRC_O3)